diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 7516acca09c8685cde73b55d448f3f29614da9ec..e2148345cd2dfb9ced15a5f56d3f516f6560ae91 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,5 +1,48 @@
 2003-05-01  Nathan Sidwell  <nathan@codesourcery.com>
 
+	* input.h (lineno): Rename to ...
+	(input_line): ... here.
+	* tree.h (lineno): Rename to ...
+	(input_line): ... here.
+	* scan.h (lineno): Rename to ...
+	(input_line): ... here.
+	* toplev.c (lineno): Rename to ...
+	(input_line): ... here.
+	(push_srcloc, pop_srcloc):  Rename lineno to input_line.
+	* c-common.c (c_expand_start_cond, fname_decl): Likewise.
+	* c-decl.c (poplevel, pop_label_level, lookup_label, lookup_tag,
+	store_parm_decls, c_expand_body_1): Likewise.
+	* c-errors.c (pedwarn_c99): Likewise.
+	* c-format.c (status_warning): Likewise.
+	* c-lex.c (fe_file_change, cb_def_pragma, c_lex): Likewise.
+	* c-opts.c (c_common_post_options, c_common_parse_file): Likewise.
+	* c-parse.in (save_filename, maybe_type_qual, ifc): Likwise.
+	* c-semantics.c (finish_stmt_tree, build_stmt, emit_local_var,
+	gentrtl_goto_stmt, genrtl_expr_stmt_value, genrtl_decl_stmt,
+	genrtl_if_stmt, genrtl_while_stmt, genrtl_do_stmt,
+	genrtl_return_stmt, genrtl_for_stmt, build_break_stmt,
+	build_continue_stmt, genrtl_switch_stmt, genrtl_asm_stmt,
+	prep_stmt, find_reachable_label, expand_unreachable_stmt): Likewise.
+	* coverage.c (create_coverage): Likewise.
+	* diagnostic.c (pedwarn, sorry, error, fatal_error,
+	internal_error, warning, diagnostic_report_current_module,
+	inform): Likewise.
+	* expr.c (expand_expr): Likewise.
+	* integrate.c (expand_inline_function,
+	output_inline_function): Likewise.
+	* rtl-error.c (file_and_line_for_asm): Likewise.
+	* tree-inline.c (find_alloca_call, find_builtin_longjmp_call,
+	walk_tree): Likewise.
+	* tree.c (make_node): Likewise.
+	* ada, cp, f, java, objc, treelang: Likewise.
+	* objc/objc-act.c (objc_init): Rename lineno to input_line.
+	(build_module_descriptor, build_selector_translation_table,
+	build_protocol_template, build_method_prototype_list_template,
+	build_category_template, build_selector_table,
+	build_class_template, build_super_template, build_ivar_template,
+	build_ivar_list_template, build_method_list_template,
+	build_method_template, add_instance_variable): Likewise.
+
 	* dwarf2out.c (dwarf2out_init, dwarf2out_finish): Change parameter
 	name from input_filename.
 
diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index e3347edab91aef79d2423a20128e9f4a14bd28ec..31971529fef3365f8e8132721dc896c131163a65 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,11 @@
+2003-05-01  Nathan Sidwell  <nathan@codesourcery.com>
+
+	* trans.c (build_unit_elab, set_lineno): Rename lineno to
+	input_line. 
+	* utils.c (pushdecl, create_label_decl, begin_subprog_body,
+	end_subprog_body): Likewise.
+	* utils2.c (build_call_raise): Likewise.
+
 2003-05-01  Laurent Guerby <guerby@acm.org>
 
         PR ada/10546 
diff --git a/gcc/ada/gigi.h b/gcc/ada/gigi.h
index 4094f4902f86cfafb79819c7a79f088047b31ed5..8ad8a2a26fd9ed8a7ed43194d369d6e20ec7d4df 100644
--- a/gcc/ada/gigi.h
+++ b/gcc/ada/gigi.h
@@ -7,7 +7,7 @@
  *                              C Header File                               *
  *                                                                          *
  *                                                                          *
- *          Copyright (C) 1992-2002 Free Software Foundation, Inc.          *
+ *          Copyright (C) 1992-2003 Free Software Foundation, Inc.          *
  *                                                                          *
  * GNAT is free software;  you can  redistribute it  and/or modify it under *
  * terms of the  GNU General Public License as published  by the Free Soft- *
@@ -192,9 +192,9 @@ extern tree gnat_to_gnu		PARAMS ((Node_Id));
 
 extern void process_type	PARAMS ((Entity_Id));
 
-/* Determine the input_filename and the lineno from the source location
+/* Determine the input_filename and the input_line from the source location
    (Sloc) of GNAT_NODE node.  Set the global variable input_filename and
-   lineno.  If WRITE_NOTE_P is true, emit a line number note. */
+   input_line.  If WRITE_NOTE_P is true, emit a line number note. */
 extern void set_lineno		PARAMS ((Node_Id, int));
 
 /* Post an error message.  MSG is the error message, properly annotated.
diff --git a/gcc/ada/trans.c b/gcc/ada/trans.c
index 797671de7d3ab204dfd1f2f7361dc5354cf2e47b..be5c656127a022dc01551389c5bf53cd24efebd5 100644
--- a/gcc/ada/trans.c
+++ b/gcc/ada/trans.c
@@ -7,7 +7,7 @@
  *                          C Implementation File                           *
  *                                                                          *
  *                                                                          *
- *          Copyright (C) 1992-2002, Free Software Foundation, Inc.         *
+ *          Copyright (C) 1992-2003, Free Software Foundation, Inc.         *
  *                                                                          *
  * GNAT is free software;  you can  redistribute it  and/or modify it under *
  * terms of the  GNU General Public License as published  by the Free Soft- *
@@ -5343,7 +5343,7 @@ build_unit_elab (gnat_unit, body_p, gnu_elab_list)
 	tree lhs = TREE_PURPOSE (gnu_elab_list);
 
 	input_filename = DECL_SOURCE_FILE (lhs);
-	lineno = DECL_SOURCE_LINE (lhs);
+	input_line = DECL_SOURCE_LINE (lhs);
 
 	/* If LHS has a padded type, convert it to the unpadded type
 	   so the assignment is done properly.  */
@@ -5414,7 +5414,7 @@ set_lineno (gnat_node, write_note_p)
       (get_identifier
        (Get_Name_String
 	(Reference_Name (Get_Source_File_Index (source_location)))));;
-  lineno = Get_Logical_Line_Number (source_location);
+  input_line = Get_Logical_Line_Number (source_location);
 
   if (write_note_p)
     emit_line_note (input_filename, lineno);
diff --git a/gcc/ada/utils.c b/gcc/ada/utils.c
index d21a097cfdd02647110fe41a76e362d1cc261d3d..e74d5a20439279104538c380405a41569d359b97 100644
--- a/gcc/ada/utils.c
+++ b/gcc/ada/utils.c
@@ -7,7 +7,7 @@
  *                          C Implementation File                           *
  *                                                                          *
  *                                                                          *
- *          Copyright (C) 1992-2002, Free Software Foundation, Inc.         *
+ *          Copyright (C) 1992-2003, Free Software Foundation, Inc.         *
  *                                                                          *
  * GNAT is free software;  you can  redistribute it  and/or modify it under *
  * terms of the  GNU General Public License as published  by the Free Soft- *
@@ -479,7 +479,7 @@ pushdecl (decl)
 void
 gnat_init_decl_processing ()
 {
-  lineno = 0;
+  input_line = 0;
 
   /* Make the binding_level structure for global names.  */
   current_function_decl = 0;
@@ -1663,7 +1663,7 @@ create_label_decl (label_name)
 
   DECL_CONTEXT (label_decl)     = current_function_decl;
   DECL_MODE (label_decl)        = VOIDmode;
-  DECL_SOURCE_LINE (label_decl) = lineno;
+  DECL_SOURCE_LINE (label_decl) = input_line;
   DECL_SOURCE_FILE (label_decl) = input_filename;
 
   return label_decl;
@@ -1781,7 +1781,7 @@ begin_subprog_body (subprog_decl)
   /* Store back the PARM_DECL nodes. They appear in the right order. */
   DECL_ARGUMENTS (subprog_decl) = getdecls ();
 
-  init_function_start (subprog_decl, input_filename, lineno);
+  init_function_start (subprog_decl, input_filename, input_line);
   expand_function_start (subprog_decl, 0);
 
   /* If this function is `main', emit a call to `__main'
@@ -1808,7 +1808,7 @@ end_subprog_body ()
   /* Mark the RESULT_DECL as being in this subprogram. */
   DECL_CONTEXT (DECL_RESULT (current_function_decl)) = current_function_decl;
 
-  expand_function_end (input_filename, lineno, 0);
+  expand_function_end (input_filename, input_line, 0);
 
   /* If this is a nested function, push a new GC context.  That will keep
      local variables on the stack from being collected while we're doing
diff --git a/gcc/ada/utils2.c b/gcc/ada/utils2.c
index 21d32f9cc6e4728d3428f24ac62f9487fe46144d..1964be12276950728a27930434ff247153457b14 100644
--- a/gcc/ada/utils2.c
+++ b/gcc/ada/utils2.c
@@ -7,7 +7,7 @@
  *                          C Implementation File                           *
  *                                                                          *
  *                                                                          *
- *          Copyright (C) 1992-2002, Free Software Foundation, Inc.         *
+ *          Copyright (C) 1992-2003, Free Software Foundation, Inc.         *
  *                                                                          *
  * GNAT is free software;  you can  redistribute it  and/or modify it under *
  * terms of the  GNU General Public License as published  by the Free Soft- *
@@ -1508,7 +1508,7 @@ build_call_raise (msg)
     build_call_2_expr (fndecl,
 		       build1 (ADDR_EXPR, build_pointer_type (char_type_node),
 			       filename),
-		       build_int_2 (lineno, 0));
+		       build_int_2 (input_line, 0));
 }
 
 /* Return a CONSTRUCTOR of TYPE whose list is LIST.  */
diff --git a/gcc/c-common.c b/gcc/c-common.c
index 4ebddbd613a46ebab78a1397bd2086dbeb90f669..c7e1cb03f88e88898c487ccf2ab0ce011202cd78 100644
--- a/gcc/c-common.c
+++ b/gcc/c-common.c
@@ -919,7 +919,7 @@ c_expand_start_cond (cond, compstmt_count, if_stmt)
   /* Record this if statement.  */
   if_stack[if_stack_pointer].compstmt_count = compstmt_count;
   if_stack[if_stack_pointer].locus.file = input_filename;
-  if_stack[if_stack_pointer].locus.line = lineno;
+  if_stack[if_stack_pointer].locus.line = input_line;
   if_stack[if_stack_pointer].needs_warning = 0;
   if_stack[if_stack_pointer].if_stmt = if_stmt;
   if_stack_pointer++;
@@ -1158,8 +1158,8 @@ fname_decl (rid, id)
 	 beginning of the function and this line number will be wrong.
 	 To avoid this problem set the lineno to 0 here; that prevents
 	 it from appearing in the RTL.  */
-      int saved_lineno = lineno;
-      lineno = 0;
+      int saved_lineno = input_line;
+      input_line = 0;
       
       decl = (*make_fname_decl) (id, fname_vars[ix].pretty);
       if (last_tree != saved_last_tree)
@@ -1175,7 +1175,7 @@ fname_decl (rid, id)
 						 saved_function_name_decls);
 	}
       *fname_vars[ix].decl = decl;
-      lineno = saved_lineno;
+      input_line = saved_lineno;
     }
   if (!ix && !current_function_decl)
     pedwarn_with_decl (decl, "`%s' is not defined outside of function scope");
diff --git a/gcc/c-decl.c b/gcc/c-decl.c
index e16c2b6205c735940666c18538c5586e7c7bb397..e35944e79179454f4a53d123792f9c3473ac0a76 100644
--- a/gcc/c-decl.c
+++ b/gcc/c-decl.c
@@ -617,7 +617,7 @@ poplevel (keep, reverse, functionbody)
 	    {
 	      error_with_decl (label, "label `%s' used but not defined");
 	      /* Avoid crashing later.  */
-	      define_label (input_filename, lineno,
+	      define_label (input_filename, input_line,
 			    DECL_NAME (label));
 	    }
 	  else if (warn_unused_label && !TREE_USED (label))
@@ -711,7 +711,7 @@ pop_label_level ()
 	      error_with_decl (TREE_VALUE (link),
 			       "label `%s' used but not defined");
 	      /* Avoid crashing later.  */
-	      define_label (input_filename, lineno,
+	      define_label (input_filename, input_line,
 			    DECL_NAME (TREE_VALUE (link)));
 	    }
 	  else if (warn_unused_label && !TREE_USED (TREE_VALUE (link)))
@@ -2019,7 +2019,7 @@ lookup_label (id)
 
   /* Say where one reference is to the label,
      for the sake of the error if it is not defined.  */
-  DECL_SOURCE_LINE (decl) = lineno;
+  DECL_SOURCE_LINE (decl) = input_line;
   DECL_SOURCE_FILE (decl) = input_filename;
 
   IDENTIFIER_LABEL_VALUE (id) = decl;
@@ -2184,7 +2184,7 @@ lookup_tag (code, name, thislevel_only)
       /* Definition isn't the kind we were looking for.  */
       pending_invalid_xref = name;
       pending_invalid_xref_file = input_filename;
-      pending_invalid_xref_line = lineno;
+      pending_invalid_xref_line = input_line;
 
       /* If in the same binding level as a declaration as a tag
 	 of a different type, this must not be allowed to
@@ -6079,7 +6079,7 @@ store_parm_decls ()
   gen_aux_info_record (fndecl, 1, 0, prototype);
 
   /* Initialize the RTL code for the function.  */
-  init_function_start (fndecl, input_filename, lineno);
+  init_function_start (fndecl, input_filename, input_line);
 
   /* Begin the statement tree for this function.  */
   begin_stmt_tree (&DECL_SAVED_TREE (current_function_decl));
@@ -6339,7 +6339,7 @@ c_expand_body_1 (fndecl, nested_p)
   current_function_decl = fndecl;
   input_filename = DECL_SOURCE_FILE (fndecl);
   init_function_start (fndecl, input_filename, DECL_SOURCE_LINE (fndecl));
-  lineno = DECL_SOURCE_LINE (fndecl);
+  input_line = DECL_SOURCE_LINE (fndecl);
 
   /* This function is being processed in whole-function mode.  */
   cfun->x_whole_function_mode_p = 1;
@@ -6384,7 +6384,7 @@ c_expand_body_1 (fndecl, nested_p)
     (*lang_expand_function_end) ();
 
   /* Generate rtl for function exit.  */
-  expand_function_end (input_filename, lineno, 0);
+  expand_function_end (input_filename, input_line, 0);
 
   /* If this is a nested function, protect the local variables in the stack
      above us from being collected while we're compiling this function.  */
diff --git a/gcc/c-errors.c b/gcc/c-errors.c
index d906357a99dd1a72bd0366fb92da1d260fe0f13b..3f3f69039de27264676622558348e15739c3f99e 100644
--- a/gcc/c-errors.c
+++ b/gcc/c-errors.c
@@ -1,5 +1,5 @@
 /* Various diagnostic subroutines for the GNU C language.
-   Copyright (C) 2000, 2001 Free Software Foundation, Inc.
+   Copyright (C) 2000, 2001, 2003 Free Software Foundation, Inc.
    Contributed by Gabriel Dos Reis <gdr@codesourcery.com>
 
 This file is part of GCC.
@@ -38,7 +38,7 @@ pedwarn_c99 VPARAMS ((const char *msgid, ...))
   VA_OPEN (ap, msgid);
   VA_FIXEDARG (ap, const char *, msgid);
 
-  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, input_line,
                        flag_isoc99 ? pedantic_error_kind () : DK_WARNING);
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
diff --git a/gcc/c-format.c b/gcc/c-format.c
index 7bd654f6b2b6901053c0ab196fb8c08842ab6caa..bf50c8636223798bd39c523a7591e44c5b737662 100644
--- a/gcc/c-format.c
+++ b/gcc/c-format.c
@@ -1,6 +1,6 @@
 /* Check calls to formatted I/O functions (-Wformat).
    Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000,
-   2001, 2002 Free Software Foundation, Inc.
+   2001, 2002, 2003 Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -1009,8 +1009,8 @@ status_warning VPARAMS ((int *status, const char *msgid, ...))
   else
     {
       /* This duplicates the warning function behavior.  */
-      diagnostic_set_info (&diagnostic, _(msgid), &ap, input_filename, lineno,
-                           DK_WARNING);
+      diagnostic_set_info (&diagnostic, _(msgid), &ap,
+			   input_filename, input_line, DK_WARNING);
       report_diagnostic (&diagnostic);
     }
 
diff --git a/gcc/c-lex.c b/gcc/c-lex.c
index eb0934c1158f28b9ce1d46267e73ed3efe4bff52..ea0f80c7b83263987807a4b4d9e7852d3db771b9 100644
--- a/gcc/c-lex.c
+++ b/gcc/c-lex.c
@@ -228,7 +228,7 @@ fe_file_change (new_map)
 	{
           int included_at = SOURCE_LINE (new_map - 1, new_map->from_line - 1);
 
-	  lineno = included_at;
+	  input_line = included_at;
 	  push_srcloc (new_map->to_file, 1);
 	  (*debug_hooks->start_source_file) (included_at, new_map->to_file);
 #ifndef NO_IMPLICIT_EXTERN_C
@@ -260,7 +260,7 @@ fe_file_change (new_map)
   update_header_times (new_map->to_file);
   in_system_header = new_map->sysp != 0;
   input_filename = new_map->to_file;
-  lineno = to_line;
+  input_line = to_line;
   map = new_map;
 
   /* Hook for C++.  */
@@ -290,7 +290,7 @@ cb_def_pragma (pfile, line)
 	    name = cpp_token_as_text (pfile, s);
 	}
 
-      lineno = SOURCE_LINE (map, line);
+      input_line = SOURCE_LINE (map, line);
       warning ("ignoring #pragma %s %s", space, name);
     }
 }
@@ -333,7 +333,7 @@ c_lex (value)
   /* The C++ front end does horrible things with the current line
      number.  To ensure an accurate line number, we must reset it
      every time we return a token.  */
-  lineno = src_lineno;
+  input_line = src_lineno;
 
   *value = NULL_TREE;
   switch (tok->type)
diff --git a/gcc/c-opts.c b/gcc/c-opts.c
index 5de5019499b713775f64005d58fe4083f7f61a9e..ee7be16ce1c8d6b4c343fe396cda74f25639c218 100644
--- a/gcc/c-opts.c
+++ b/gcc/c-opts.c
@@ -1564,7 +1564,7 @@ c_common_post_options (pfilename)
       init_c_lex ();
 
       /* Yuk.  WTF is this?  I do know ObjC relies on it somewhere.  */
-      lineno = 0;
+      input_line = 0;
     }
 
   cpp_get_callbacks (parse_in)->file_change = cb_file_change;
@@ -1572,8 +1572,8 @@ c_common_post_options (pfilename)
   /* NOTE: we use in_fname here, not the one supplied.  */
   *pfilename = cpp_read_main_file (parse_in, in_fname);
 
-  saved_lineno = lineno;
-  lineno = 0;
+  saved_lineno = input_line;
+  input_line = 0;
 
   /* If an error has occurred in cpplib, note it so we fail
      immediately.  */
@@ -1586,7 +1586,7 @@ c_common_post_options (pfilename)
 bool
 c_common_init ()
 {
-  lineno = saved_lineno;
+  input_line = saved_lineno;
 
   /* Set up preprocessor arithmetic.  Must be done after call to
      c_common_nodes_and_builtins for type nodes to be good.  */
@@ -1624,7 +1624,7 @@ c_common_parse_file (set_yydebug)
   warning ("YYDEBUG not defined");
 #endif
 
-  (*debug_hooks->start_source_file) (lineno, input_filename);
+  (*debug_hooks->start_source_file) (input_line, input_filename);
   finish_options();
   pch_init();
   yyparse ();
diff --git a/gcc/c-parse.in b/gcc/c-parse.in
index 72fbb68ebba4774614503f7d557c98951c8bc21a..807f90a9048918dd5383420e0ccffa3d42e6e061 100644
--- a/gcc/c-parse.in
+++ b/gcc/c-parse.in
@@ -1,6 +1,6 @@
-/* YACC parser for C syntax and for Objective C.  -*-c-*-
+ /* YACC parser for C syntax and for Objective C.  -*-c-*-
    Copyright (C) 1987, 1988, 1989, 1992, 1993, 1994, 1995, 1996,
-   1997, 1998, 1999, 2000, 2001, 2002 Free Software Foundation, Inc.
+   1997, 1998, 1999, 2000, 2001, 2002, 2003 Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -138,6 +138,7 @@ do {									\
 
 /* String constants in raw form.
    yylval is a STRING_CST node.  */
+
 %token STRING
 
 /* "...", used for functions with variable arglists.  */
@@ -2250,7 +2251,7 @@ save_filename:
 save_lineno:
 		{ if (yychar == YYEMPTY)
 		    yychar = YYLEX;
-		  $$ = lineno; }
+		  $$ = input_line; }
 	;
 
 lineno_labeled_stmt:
@@ -2455,10 +2456,10 @@ label:	  CASE expr_no_commas ':'
 
 maybe_type_qual:
 	/* empty */
-		{ emit_line_note (input_filename, lineno);
+		{ emit_line_note (input_filename, input_line);
 		  $$ = NULL_TREE; }
 	| TYPE_QUAL
-		{ emit_line_note (input_filename, lineno); }
+		{ emit_line_note (input_filename, input_line); }
 	;
 
 xexpr:
@@ -3690,11 +3691,11 @@ ifc
       static int last_lineno = 0;
       static const char *last_input_filename = 0;
       if (warn_traditional && !in_system_header
-	  && (lineno != last_lineno || !last_input_filename ||
+	  && (input_line != last_lineno || !last_input_filename ||
 	      strcmp (last_input_filename, input_filename)))
 	{
 	  warning ("traditional C rejects string concatenation");
-	  last_lineno = lineno;
+	  last_lineno = input_line;
 	  last_input_filename = input_filename;
 	}
 end ifc
diff --git a/gcc/c-semantics.c b/gcc/c-semantics.c
index fc7ccb745ff49e79a775e8cb5bba7785485e3280..19ea48ebd12d0160b99c3fc7567ceea9ca7e4e2f 100644
--- a/gcc/c-semantics.c
+++ b/gcc/c-semantics.c
@@ -181,7 +181,7 @@ finish_stmt_tree (t)
     {
       /* The line-number recorded in the outermost statement in a function
 	 is the line number of the end of the function.  */
-      STMT_LINENO (stmt) = lineno;
+      STMT_LINENO (stmt) = input_line;
       STMT_LINENO_FOR_FN_P (stmt) = 1;
     }
 }
@@ -204,7 +204,7 @@ build_stmt VPARAMS ((enum tree_code code, ...))
 
   t = make_node (code);
   length = TREE_CODE_LENGTH (code);
-  STMT_LINENO (t) = lineno;
+  STMT_LINENO (t) = input_line;
 
   for (i = 0; i < length; i++)
     TREE_OPERAND (t, i) = va_arg (p, tree);
@@ -301,7 +301,7 @@ emit_local_var (decl)
 void
 genrtl_do_pushlevel ()
 {
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   clear_last_expr ();
 }
 
@@ -319,7 +319,7 @@ genrtl_goto_stmt (destination)
   if (TREE_CODE (destination) == LABEL_DECL)
     TREE_USED (destination) = 1;
   
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   
   if (TREE_CODE (destination) == LABEL_DECL)
     {
@@ -355,7 +355,7 @@ genrtl_expr_stmt_value (expr, want_value, maybe_last)
 {
   if (expr != NULL_TREE)
     {
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       
       if (stmts_are_full_exprs_p ())
 	expand_start_target_temps ();
@@ -375,7 +375,7 @@ genrtl_decl_stmt (t)
      tree t;
 {
   tree decl;
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   decl = DECL_STMT_DECL (t);
   /* If this is a declaration for an automatic local
      variable, initialize it.  Note that we might also see a
@@ -412,7 +412,7 @@ genrtl_if_stmt (t)
   tree cond;
   genrtl_do_pushlevel ();
   cond = expand_cond (IF_COND (t));
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   expand_start_cond (cond, 0);
   if (THEN_CLAUSE (t))
     {
@@ -442,14 +442,14 @@ genrtl_while_stmt (t)
   tree cond = WHILE_COND (t);
 
   emit_nop ();
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   expand_start_loop (1); 
   genrtl_do_pushlevel ();
 
   if (cond && !integer_nonzerop (cond))
     {
       cond = expand_cond (cond);
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       expand_exit_loop_top_cond (0, cond);
       genrtl_do_pushlevel ();
     }
@@ -481,25 +481,25 @@ genrtl_do_stmt (t)
   else if (integer_nonzerop (cond))
     {
       emit_nop ();
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       expand_start_loop (1);
 
       expand_stmt (DO_BODY (t));
 
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       expand_end_loop ();
     }
   else
     {
       emit_nop ();
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       expand_start_loop_continue_elsewhere (1);
 
       expand_stmt (DO_BODY (t));
 
       expand_loop_continue_here ();
       cond = expand_cond (cond);
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       expand_exit_loop_if_false (0, cond);
       expand_end_loop ();
     }
@@ -524,7 +524,7 @@ genrtl_return_stmt (stmt)
 
   expr = RETURN_STMT_EXPR (stmt);
 
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   if (!expr)
     expand_null_return ();
   else
@@ -552,7 +552,7 @@ genrtl_for_stmt (t)
 
   /* Expand the initialization.  */
   emit_nop ();
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   if (FOR_EXPR (t))
     expand_start_loop_continue_elsewhere (1); 
   else
@@ -562,13 +562,13 @@ genrtl_for_stmt (t)
   /* Save the filename and line number so that we expand the FOR_EXPR
      we can reset them back to the saved values.  */
   saved_filename = input_filename;
-  saved_lineno = lineno;
+  saved_lineno = input_line;
 
   /* Expand the condition.  */
   if (cond && !integer_nonzerop (cond))
     {
       cond = expand_cond (cond);
-      emit_line_note (input_filename, lineno);
+      emit_line_note (input_filename, input_line);
       expand_exit_loop_top_cond (0, cond);
       genrtl_do_pushlevel ();
     }
@@ -578,8 +578,8 @@ genrtl_for_stmt (t)
 
   /* Expand the increment expression.  */
   input_filename = saved_filename;
-  lineno = saved_lineno;
-  emit_line_note (input_filename, lineno);
+  input_line = saved_lineno;
+  emit_line_note (input_filename, input_line);
   if (FOR_EXPR (t))
     {
       expand_loop_continue_here ();
@@ -601,7 +601,7 @@ build_break_stmt ()
 void
 genrtl_break_stmt ()
 {
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   if ( ! expand_exit_something ())
     error ("break statement not within loop or switch");
 }
@@ -619,7 +619,7 @@ build_continue_stmt ()
 void
 genrtl_continue_stmt ()
 {
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   if (! expand_continue_loop (0))
     error ("continue statement not within a loop");   
 }
@@ -685,7 +685,7 @@ genrtl_switch_stmt (t)
        crash.  */
     cond = boolean_false_node;
 
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   expand_start_case (1, cond, TREE_TYPE (cond), "switch statement");
   expand_unreachable_stmt (SWITCH_BODY (t), warn_notreached);
   expand_end_case_type (cond, SWITCH_TYPE (t));
@@ -768,13 +768,13 @@ genrtl_asm_stmt (cv_qualifier, string, output_operands,
       cv_qualifier = NULL_TREE;
     }
 
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   if (asm_input_p)
     expand_asm (string, cv_qualifier != NULL_TREE);
   else
     c_expand_asm_operands (string, output_operands, input_operands, 
 			   clobbers, cv_qualifier != NULL_TREE,
-			   input_filename, lineno);
+			   input_filename, input_line);
 }
 
 /* Generate the RTL for a CLEANUP_STMT.  */
@@ -796,7 +796,7 @@ prep_stmt (t)
      tree t;
 {
   if (!STMT_LINENO_FOR_FN_P (t))
-    lineno = STMT_LINENO (t);
+    input_line = STMT_LINENO (t);
   current_stmt_tree ()->stmts_are_full_exprs_p = STMT_IS_FULL_EXPR_P (t);
 }
 
@@ -951,11 +951,11 @@ static tree
 find_reachable_label (exp)
      tree exp;
 {
-  int line = lineno;
+  int line = input_line;
   const char *file = input_filename;
   tree ret = walk_tree (&exp, find_reachable_label_1, NULL, NULL);
   input_filename = file;
-  lineno = line;
+  input_line = line;
   return ret;
 }
 
@@ -1025,7 +1025,7 @@ expand_unreachable_stmt (t, warn)
 	  case IF_STMT:
 	  case RETURN_STMT:
 	    if (!STMT_LINENO_FOR_FN_P (t))
-	      lineno = STMT_LINENO (t);
+	      input_line = STMT_LINENO (t);
 	    warning("will never be executed");
 	    warn = false;
 	    break;
diff --git a/gcc/coverage.c b/gcc/coverage.c
index 9d7e0893905ea819b9c3acba61248bcbd6b985c0..6d8ae9a55fba15dbe1462422931d014eb616df19 100644
--- a/gcc/coverage.c
+++ b/gcc/coverage.c
@@ -800,7 +800,7 @@ create_coverage ()
   current_function_decl = ctor;
   DECL_INITIAL (ctor) = error_mark_node;
   make_decl_rtl (ctor, NULL);
-  init_function_start (ctor, input_filename, lineno);
+  init_function_start (ctor, input_filename, input_line);
   (*lang_hooks.decls.pushlevel) (0);
   expand_function_start (ctor, 0);
   cfun->arc_profile = 0;
@@ -810,7 +810,7 @@ create_coverage ()
   emit_library_call (gcov_init_libfunc, LCT_NORMAL, VOIDmode, 1,
 		     gcov_info_address, Pmode);
 
-  expand_function_end (input_filename, lineno, 0);
+  expand_function_end (input_filename, input_line, 0);
   (*lang_hooks.decls.poplevel) (1, 0, 1);
 
   /* Since ctor isn't in the list of globals, it would never be emitted
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index 7dbfa768edd8bbf45e1dc8ede8dfdb84c534d03d..e45781eda57e596e6f934c327fe7c35f3fd2677e 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -5252,7 +5252,7 @@ tree
 finish_struct (tree t, tree attributes)
 {
   const char *saved_filename = input_filename;
-  int saved_lineno = lineno;
+  int saved_lineno = input_line;
 
   /* Now that we've got all the field declarations, reverse everything
      as necessary.  */
@@ -5263,7 +5263,7 @@ finish_struct (tree t, tree attributes)
   /* Nadger the current location so that diagnostics point to the start of
      the struct, not the end.  */
   input_filename = DECL_SOURCE_FILE (TYPE_NAME (t));
-  lineno = DECL_SOURCE_LINE (TYPE_NAME (t));
+  input_line = DECL_SOURCE_LINE (TYPE_NAME (t));
 
   if (processing_template_decl)
     {
@@ -5274,7 +5274,7 @@ finish_struct (tree t, tree attributes)
     finish_struct_1 (t);
 
   input_filename = saved_filename;
-  lineno = saved_lineno;
+  input_line = saved_lineno;
 
   TYPE_BEING_DEFINED (t) = 0;
 
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index 2c911a50329e763d2a9a06aa16a2244ab773b34a..6e04cef2e19af3d2de84b08df2daef5f02acf1b1 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -495,7 +495,7 @@ push_binding_level (struct cp_binding_level *newlevel,
   newlevel->binding_depth = binding_depth;
   indent ();
   fprintf (stderr, "push %s level 0x%08x line %d\n",
-	   (is_class_level) ? "class" : "block", newlevel, lineno);
+	   (is_class_level) ? "class" : "block", newlevel, input_line);
   is_class_level = 0;
   binding_depth++;
 #endif /* defined(DEBUG_BINDING_LEVELS) */
@@ -532,7 +532,7 @@ pop_binding_level (void)
   indent ();
   fprintf (stderr, "pop  %s level 0x%08x line %d\n",
 	  (is_class_level) ? "class" : "block",
-	  current_binding_level, lineno);
+	  current_binding_level, input_line);
   if (is_class_level != (current_binding_level == class_binding_level))
     {
       indent ();
@@ -571,7 +571,7 @@ suspend_binding_level (void)
   indent ();
   fprintf (stderr, "suspend  %s level 0x%08x line %d\n",
 	  (is_class_level) ? "class" : "block",
-	  current_binding_level, lineno);
+	  current_binding_level, input_line);
   if (is_class_level != (current_binding_level == class_binding_level))
     {
       indent ();
@@ -596,7 +596,7 @@ resume_binding_level (struct cp_binding_level* b)
   b->binding_depth = binding_depth;
   indent ();
   fprintf (stderr, "resume %s level 0x%08x line %d\n",
-	   (is_class_level) ? "class" : "block", b, lineno);
+	   (is_class_level) ? "class" : "block", b, input_line);
   is_class_level = 0;
   binding_depth++;
 #endif /* defined(DEBUG_BINDING_LEVELS) */
@@ -4598,7 +4598,7 @@ make_label_decl (tree id, int local_p)
 
   /* Say where one reference is to the label, for the sake of the
      error if it is not defined.  */
-  DECL_SOURCE_LINE (decl) = lineno;
+  DECL_SOURCE_LINE (decl) = input_line;
   DECL_SOURCE_FILE (decl) = input_filename;
 
   /* Record the fact that this identifier is bound to this label.  */
@@ -4625,7 +4625,7 @@ use_label (tree decl)
       new_ent->label_decl = decl;
       new_ent->names_in_scope = current_binding_level->names;
       new_ent->binding_level = current_binding_level;
-      new_ent->o_goto_locus.line = lineno;
+      new_ent->o_goto_locus.line = input_line;
       new_ent->o_goto_locus.file = input_filename;
       new_ent->next = named_label_uses;
       named_label_uses = new_ent;
@@ -13486,7 +13486,7 @@ start_function (tree declspecs, tree declarator, tree attrs, int flags)
      CFUN set up, and our per-function variables initialized.
      FIXME factor out the non-RTL stuff.  */
   bl = current_binding_level;
-  init_function_start (decl1, input_filename, lineno);
+  init_function_start (decl1, input_filename, input_line);
   current_binding_level = bl;
 
   /* Even though we're inside a function body, we still don't want to
diff --git a/gcc/cp/decl2.c b/gcc/cp/decl2.c
index 00a77dfa30a83c41a0ab3f4e380a1364c92ecb5a..71192ef7892794b2f1d8e67b51e7591ad1c6a71d 100644
--- a/gcc/cp/decl2.c
+++ b/gcc/cp/decl2.c
@@ -178,17 +178,17 @@ warn_if_unknown_interface (tree decl)
   if (flag_alt_external_templates)
     {
       tree til = tinst_for_decl ();
-      int sl = lineno;
+      int sl = input_line;
       const char *sf = input_filename;
 
       if (til)
 	{
-	  lineno = TINST_LINE (til);
+	  input_line = TINST_LINE (til);
 	  input_filename = TINST_FILE (til);
 	}
       warning ("template `%#D' instantiated in file without #pragma interface",
 		  decl);
-      lineno = sl;
+      input_line = sl;
       input_filename = sf;
     }
   else
@@ -2234,7 +2234,7 @@ start_static_initialization_or_destruction (tree decl, int initp)
      that the debugger will show somewhat sensible file and line
      information.  */
   input_filename = DECL_SOURCE_FILE (decl);
-  lineno = DECL_SOURCE_LINE (decl);
+  input_line = DECL_SOURCE_LINE (decl);
 
   /* Because of:
 
@@ -2475,7 +2475,7 @@ generate_ctor_or_dtor_function (bool constructor_p, int priority,
   size_t i;
 
   input_filename = locus->file;
-  lineno = locus->line++;
+  input_line = locus->line++;
   
   /* We use `I' to indicate initialization and `D' to indicate
      destruction.  */
@@ -2555,7 +2555,7 @@ finish_file ()
   unsigned ssdf_count = 0;
 
   locus.file = input_filename;
-  locus.line = lineno;
+  locus.line = input_line;
   at_eof = 1;
 
   /* Bad parse errors.  Just forget about it.  */
@@ -2567,7 +2567,7 @@ finish_file ()
 
   /* Otherwise, GDB can get confused, because in only knows
      about source for LINENO-1 lines.  */
-  lineno -= 1;
+  input_line -= 1;
 
   interface_unknown = 1;
   interface_only = 0;
@@ -2687,7 +2687,7 @@ finish_file ()
 	  /* Set the line and file, so that it is obviously not from
 	     the source file.  */
 	  input_filename = locus.file;
-	  lineno = locus.line;
+	  input_line = locus.line;
 	  ssdf_body = start_static_storage_duration_function (ssdf_count);
 
 	  /* Make sure the back end knows about all the variables.  */
@@ -2716,7 +2716,7 @@ finish_file ()
 	  /* Finish up the static storage duration function for this
 	     round.  */
 	  input_filename = locus.file;
-	  lineno = locus.line;
+	  input_line = locus.line;
 	  finish_static_storage_duration_function (ssdf_body);
 
 	  /* All those initializations and finalizations might cause
@@ -2906,7 +2906,7 @@ finish_file ()
       dump_time_statistics ();
     }
   input_filename = locus.file;
-  lineno = locus.line;
+  input_line = locus.line;
 }
 
 /* T is the parse tree for an expression.  Return the expression after
diff --git a/gcc/cp/error.c b/gcc/cp/error.c
index 3e299de57c861ab9b93c900b388937e89b56a624..ee92aa842d982da97c9a97121e263657e34548ad 100644
--- a/gcc/cp/error.c
+++ b/gcc/cp/error.c
@@ -1,7 +1,7 @@
 /* Call-backs for C++ error reporting.
    This code is non-reentrant.
-   Copyright (C) 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2002
-   Free Software Foundation, Inc.
+   Copyright (C) 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2002,
+   2003 Free Software Foundation, Inc.
    This file is part of GCC.
 
 GCC is free software; you can redistribute it and/or modify
@@ -2159,7 +2159,7 @@ cp_line_of (tree t)
     line = DECL_SOURCE_LINE (t);
 
   if (line == 0)
-    return lineno;
+    return input_line;
 
   return line;
 }
@@ -2406,7 +2406,7 @@ static void
 print_instantiation_full_context (diagnostic_context *context)
 {
   tree p = current_instantiation ();
-  int line = lineno;
+  int line = input_line;
   const char *file = input_filename;
 
   if (p)
@@ -2468,7 +2468,7 @@ void
 print_instantiation_context (void)
 {
   print_instantiation_partial_context
-    (global_dc, current_instantiation (), input_filename, lineno);
+    (global_dc, current_instantiation (), input_filename, input_line);
   diagnostic_flush_buffer (global_dc);
 }
 
diff --git a/gcc/cp/except.c b/gcc/cp/except.c
index ae37b290c1aaea5282630cfa4c6c1903c763024a..b8576be061a827d94116b8ff8dafab283eeaae70 100644
--- a/gcc/cp/except.c
+++ b/gcc/cp/except.c
@@ -915,10 +915,10 @@ check_handlers_1 (tree master, tree handlers)
     if (TREE_TYPE (handler)
 	&& can_convert_eh (type, TREE_TYPE (handler)))
       {
-	lineno = STMT_LINENO (handler);
+	input_line = STMT_LINENO (handler);
 	warning ("exception of type `%T' will be caught",
 		    TREE_TYPE (handler));
-	lineno = STMT_LINENO (master);
+	input_line = STMT_LINENO (master);
 	warning ("   by earlier handler for `%T'", type);
 	break;
       }
@@ -930,19 +930,20 @@ void
 check_handlers (tree handlers)
 {
   tree handler;
-  int save_line = lineno;
+  int save_line = input_line;
+  
   for (handler = handlers; handler; handler = TREE_CHAIN (handler))
     {
       if (TREE_CHAIN (handler) == NULL_TREE)
 	/* No more handlers; nothing to shadow.  */;
       else if (TREE_TYPE (handler) == NULL_TREE)
 	{
-	  lineno = STMT_LINENO (handler);
+	  input_line = STMT_LINENO (handler);
 	  pedwarn
 	    ("`...' handler must be the last handler for its try block");
 	}
       else
 	check_handlers_1 (handler, TREE_CHAIN (handler));
     }
-  lineno = save_line;
+  input_line = save_line;
 }
diff --git a/gcc/cp/init.c b/gcc/cp/init.c
index d4beb0b751cd3d3480feb074518bdf6549943ea3..96f7e77e7d03444681799e01b37ca63cbd0aac86 100644
--- a/gcc/cp/init.c
+++ b/gcc/cp/init.c
@@ -2676,7 +2676,7 @@ create_temporary_var (type)
   TREE_USED (decl) = 1;
   DECL_ARTIFICIAL (decl) = 1;
   DECL_SOURCE_FILE (decl) = input_filename;
-  DECL_SOURCE_LINE (decl) = lineno;
+  DECL_SOURCE_LINE (decl) = input_line;
   DECL_IGNORED_P (decl) = 1;
   DECL_CONTEXT (decl) = current_function_decl;
 
diff --git a/gcc/cp/method.c b/gcc/cp/method.c
index 49bb1168cfc5fab713e06ca98408464f734259a6..fd61d20cb511d73c4672b06f220aec7961bbdffd 100644
--- a/gcc/cp/method.c
+++ b/gcc/cp/method.c
@@ -1,7 +1,7 @@
 /* Handle the hair of processing (but not expanding) inline functions.
    Also manage function and variable name overloading.
    Copyright (C) 1987, 1989, 1992, 1993, 1994, 1995, 1996, 1997, 1998, 
-   1999, 2000, 2001, 2002 Free Software Foundation, Inc.
+   1999, 2000, 2001, 2002, 2003 Free Software Foundation, Inc.
    Contributed by Michael Tiemann (tiemann@cygnus.com)
 
 This file is part of GCC.
@@ -429,7 +429,7 @@ use_thunk (tree thunk_fndecl, bool emit_p)
       DECL_RESULT (thunk_fndecl)
 	= build_decl (RESULT_DECL, 0, integer_type_node);
       fnname = XSTR (XEXP (DECL_RTL (thunk_fndecl), 0), 0);
-      init_function_start (thunk_fndecl, input_filename, lineno);
+      init_function_start (thunk_fndecl, input_filename, input_line);
       current_function_is_thunk = 1;
       assemble_start_function (thunk_fndecl, fnname);
 
@@ -754,7 +754,7 @@ synthesize_method (tree fndecl)
      where the attempt to generate the function occurs, giving the
      user a hint as to why we are attempting to generate the
      function.  */
-  DECL_SOURCE_LINE (fndecl) = lineno;
+  DECL_SOURCE_LINE (fndecl) = input_line;
   DECL_SOURCE_FILE (fndecl) = input_filename;
 
   interface_unknown = 1;
diff --git a/gcc/cp/parser.c b/gcc/cp/parser.c
index 2d54e7ef84a8599ff04d6a306ea98569cbd590f5..3664302b83b75c4507af2e46452acd1710614c87 100644
--- a/gcc/cp/parser.c
+++ b/gcc/cp/parser.c
@@ -407,7 +407,7 @@ cp_lexer_set_source_position_from_token (cp_lexer *lexer ATTRIBUTE_UNUSED ,
   /* Update the line number.  */
   if (token->type != CPP_EOF)
     {
-      lineno = token->line_number;
+      input_line = token->line_number;
       input_filename = token->file_name;
     }
 }
@@ -651,7 +651,7 @@ cp_lexer_get_preprocessor_token (cp_lexer *lexer ATTRIBUTE_UNUSED ,
 	}
     }
   /* Now we've got our token.  */
-  token->line_number = lineno;
+  token->line_number = input_line;
   token->file_name = input_filename;
 
   /* Check to see if this token is a keyword.  */
diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index 73ada265efaf92a2db15e35b009cb7bbddf36cbc..45c99f9c5f1a36de91487a8fcd644c7fb8436486 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -4785,7 +4785,7 @@ push_tinst_level (d)
       return 0;
     }
 
-  new = build_expr_wfl (d, input_filename, lineno, 0);
+  new = build_expr_wfl (d, input_filename, input_line, 0);
   TREE_CHAIN (new) = current_tinst_level;
   current_tinst_level = new;
 
@@ -4809,7 +4809,7 @@ pop_tinst_level ()
 
   /* Restore the filename and line number stashed away when we started
      this instantiation.  */
-  lineno = TINST_LINE (old);
+  input_line = TINST_LINE (old);
   input_filename = TINST_FILE (old);
   extract_interface_info ();
   
@@ -4861,10 +4861,10 @@ tsubst_friend_function (decl, args)
      tree args;
 {
   tree new_friend;
-  int line = lineno;
+  int line = input_line;
   const char *file = input_filename;
 
-  lineno = DECL_SOURCE_LINE (decl);
+  input_line = DECL_SOURCE_LINE (decl);
   input_filename = DECL_SOURCE_FILE (decl);
 
   if (TREE_CODE (decl) == FUNCTION_DECL 
@@ -5072,7 +5072,7 @@ tsubst_friend_function (decl, args)
     }
 
  done:
-  lineno = line;
+  input_line = line;
   input_filename = file;
   return new_friend;
 }
@@ -5432,10 +5432,11 @@ instantiate_class_template (type)
 		{
 		  tree r;
 
-		  /* The the file and line for this declaration, to assist
-		     in error message reporting.  Since we called 
-		     push_tinst_level above, we don't need to restore these.  */
-		  lineno = DECL_SOURCE_LINE (t);
+		  /* The the file and line for this declaration, to
+		     assist in error message reporting.  Since we
+		     called push_tinst_level above, we don't need to
+		     restore these.  */
+		  input_line = DECL_SOURCE_LINE (t);
 		  input_filename = DECL_SOURCE_FILE (t);
 
 		  r = tsubst (t, args, tf_error | tf_warning, NULL_TREE);
@@ -5538,7 +5539,7 @@ instantiate_class_template (type)
      implicit functions at a predictable point, and the same point
      that would be used for non-template classes.  */
   typedecl = TYPE_MAIN_DECL (type);
-  lineno = DECL_SOURCE_LINE (typedecl);
+  input_line = DECL_SOURCE_LINE (typedecl);
   input_filename = DECL_SOURCE_FILE (typedecl);
 
   unreverse_member_declarations (type);
@@ -5883,9 +5884,9 @@ tsubst_decl (t, args, type, complain)
   tree in_decl = t;
 
   /* Set the filename and linenumber to improve error-reporting.  */
-  saved_lineno = lineno;
+  saved_lineno = input_line;
   saved_filename = input_filename;
-  lineno = DECL_SOURCE_LINE (t);
+  input_line = DECL_SOURCE_LINE (t);
   input_filename = DECL_SOURCE_FILE (t);
 
   switch (TREE_CODE (t))
@@ -6352,7 +6353,7 @@ tsubst_decl (t, args, type, complain)
     } 
 
   /* Restore the file and line information.  */
-  lineno = saved_lineno;
+  input_line = saved_lineno;
   input_filename = saved_filename;
 
   return r;
@@ -6875,7 +6876,7 @@ tsubst (t, args, complain, in_decl)
 	       message to avoid spewing a ton of messages during a
 	       single bad template instantiation.  */
 	    if (complain & tf_error
-		&& (last_line != lineno || last_file != input_filename))
+		&& (last_line != input_line || last_file != input_filename))
 	      {
 		if (TREE_CODE (type) == VOID_TYPE)
 		  error ("forming reference to void");
@@ -6883,7 +6884,7 @@ tsubst (t, args, complain, in_decl)
 		  error ("forming %s to reference type `%T'",
 			    (code == POINTER_TYPE) ? "pointer" : "reference",
 			    type);
-		last_line = lineno;
+		last_line = input_line;
 		last_file = input_filename;
 	      }
 
@@ -7779,7 +7780,7 @@ tsubst_expr (t, args, complain, in_decl)
       break;
 
     case LABEL_STMT:
-      lineno = STMT_LINENO (t);
+      input_line = STMT_LINENO (t);
       finish_label_stmt (DECL_NAME (LABEL_STMT_LABEL (t)));
       break;
 
@@ -10758,7 +10759,7 @@ instantiate_decl (d, defer_ok)
   tree spec;
   tree gen_tmpl;
   int pattern_defined;
-  int line = lineno;
+  int line = input_line;
   int need_push;
   const char *file = input_filename;
 
@@ -10824,7 +10825,7 @@ instantiate_decl (d, defer_ok)
   else
     pattern_defined = ! DECL_IN_AGGR_P (code_pattern);
 
-  lineno = DECL_SOURCE_LINE (d);
+  input_line = DECL_SOURCE_LINE (d);
   input_filename = DECL_SOURCE_FILE (d);
 
   if (pattern_defined)
@@ -10912,7 +10913,7 @@ instantiate_decl (d, defer_ok)
      because it's used by add_pending_template.  */
   else if (! pattern_defined || defer_ok)
     {
-      lineno = line;
+      input_line = line;
       input_filename = file;
 
       if (at_eof && !pattern_defined 
@@ -10941,7 +10942,7 @@ instantiate_decl (d, defer_ok)
   
   /* We already set the file and line above.  Reset them now in case
      they changed as a result of calling regenerate_decl_from_template.  */
-  lineno = DECL_SOURCE_LINE (d);
+  input_line = DECL_SOURCE_LINE (d);
   input_filename = DECL_SOURCE_FILE (d);
 
   if (TREE_CODE (d) == VAR_DECL)
@@ -11047,7 +11048,7 @@ instantiate_decl (d, defer_ok)
     pop_from_top_level ();
 
 out:
-  lineno = line;
+  input_line = line;
   input_filename = file;
 
   pop_tinst_level ();
diff --git a/gcc/cp/semantics.c b/gcc/cp/semantics.c
index cdb24f6e91017696af0ea08b0c5f9f89e53d1a92..a527abbef6456601feeefa58d60688e66bbd02c9 100644
--- a/gcc/cp/semantics.c
+++ b/gcc/cp/semantics.c
@@ -745,7 +745,7 @@ genrtl_try_block (t)
   else
     {
       if (!FN_TRY_BLOCK_P (t)) 
-	emit_line_note (input_filename, lineno);
+	emit_line_note (input_filename, input_line);
 
       expand_eh_region_start ();
       expand_stmt (TRY_STMTS (t));
@@ -1105,7 +1105,7 @@ tree
 finish_label_stmt (name)
      tree name;
 {
-  tree decl = define_label (input_filename, lineno, name);
+  tree decl = define_label (input_filename, input_line, name);
   return add_stmt (build_stmt (LABEL_STMT, decl));
 }
 
@@ -1805,7 +1805,7 @@ begin_class_definition (t)
 
   /* Update the location of the decl.  */
   DECL_SOURCE_FILE (TYPE_NAME (t)) = input_filename;
-  DECL_SOURCE_LINE (TYPE_NAME (t)) = lineno;
+  DECL_SOURCE_LINE (TYPE_NAME (t)) = input_line;
   
   if (TYPE_BEING_DEFINED (t))
     {
@@ -2386,10 +2386,10 @@ expand_body (fn)
   /* Save the current file name and line number.  When we expand the
      body of the function, we'll set LINENO and INPUT_FILENAME so that
      error-mesages come out in the right places.  */
-  saved_lineno = lineno;
+  saved_lineno = input_line;
   saved_input_filename = input_filename;
   saved_function = current_function_decl;
-  lineno = DECL_SOURCE_LINE (fn);
+  input_line = DECL_SOURCE_LINE (fn);
   input_filename = DECL_SOURCE_FILE (fn);
   current_function_decl = fn;
 
@@ -2413,7 +2413,7 @@ expand_body (fn)
 
   /* The outermost statement for a function contains the line number
      recorded when we finished processing the function.  */
-  lineno = STMT_LINENO (DECL_SAVED_TREE (fn));
+  input_line = STMT_LINENO (DECL_SAVED_TREE (fn));
 
   /* Generate code for the function.  */
   genrtl_finish_function (fn);
@@ -2433,7 +2433,7 @@ expand_body (fn)
 
   /* And restore the current source position.  */
   current_function_decl = saved_function;
-  lineno = saved_lineno;
+  input_line = saved_lineno;
   input_filename = saved_input_filename;
   extract_interface_info ();
 
@@ -2577,7 +2577,7 @@ genrtl_finish_function (fn)
   immediate_size_expand = 1;
 
   /* Generate rtl for function exit.  */
-  expand_function_end (input_filename, lineno, 0);
+  expand_function_end (input_filename, input_line, 0);
 
   /* If this is a nested function (like a template instantiation that
      we're compiling in the midst of compiling something else), push a
diff --git a/gcc/cp/tree.c b/gcc/cp/tree.c
index ee17ceaf560262cef59a9006eda044042865b873..0566a09d5c88885d7eb578773469480f22f6bb87 100644
--- a/gcc/cp/tree.c
+++ b/gcc/cp/tree.c
@@ -1512,7 +1512,7 @@ build_min_nt VPARAMS ((enum tree_code code, ...))
 
   t = make_node (code);
   length = TREE_CODE_LENGTH (code);
-  TREE_COMPLEXITY (t) = lineno;
+  TREE_COMPLEXITY (t) = input_line;
 
   for (i = 0; i < length; i++)
     {
@@ -1541,7 +1541,7 @@ build_min VPARAMS ((enum tree_code code, tree tt, ...))
   t = make_node (code);
   length = TREE_CODE_LENGTH (code);
   TREE_TYPE (t) = tt;
-  TREE_COMPLEXITY (t) = lineno;
+  TREE_COMPLEXITY (t) = input_line;
 
   for (i = 0; i < length; i++)
     {
diff --git a/gcc/diagnostic.c b/gcc/diagnostic.c
index e0e47e938bcf058214cadee4411577eed467998d..565e073c5738041931f864074ea9e85e7dee020f 100644
--- a/gcc/diagnostic.c
+++ b/gcc/diagnostic.c
@@ -1,5 +1,5 @@
 /* Language-independent diagnostic subroutines for the GNU Compiler Collection
-   Copyright (C) 1999, 2000, 2001, 2002 Free Software Foundation, Inc.
+   Copyright (C) 1999, 2000, 2001, 2002, 2003 Free Software Foundation, Inc.
    Contributed by Gabriel Dos Reis <gdr@codesourcery.com>
 
 This file is part of GCC.
@@ -961,7 +961,7 @@ pedwarn VPARAMS ((const char *msgid, ...))
   VA_OPEN (ap, msgid);
   VA_FIXEDARG (ap, const char *, msgid);
 
-  diagnostic_set_info (&diagnostic, _(msgid), &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, _(msgid), &ap, input_filename, input_line,
                        pedantic_error_kind ());
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
@@ -1019,7 +1019,7 @@ sorry VPARAMS ((const char *msgid, ...))
 
   ++sorrycount;
   diagnostic_set_info (&diagnostic, _(msgid), &ap,
-                       input_filename, lineno, DK_SORRY);
+                       input_filename, input_line, DK_SORRY);
 
   output_set_prefix
     (&global_dc->buffer, diagnostic_build_prefix (&diagnostic));
@@ -1136,7 +1136,7 @@ error VPARAMS ((const char *msgid, ...))
   VA_OPEN (ap, msgid);
   VA_FIXEDARG (ap, const char *, msgid);
 
-  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, input_line,
                        DK_ERROR);
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
@@ -1153,7 +1153,7 @@ fatal_error VPARAMS ((const char *msgid, ...))
   VA_OPEN (ap, msgid);
   VA_FIXEDARG (ap, const char *, msgid);
 
-  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, input_line,
                        DK_FATAL);
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
@@ -1177,7 +1177,7 @@ internal_error VPARAMS ((const char *msgid, ...))
   if (errorcount > 0 || sorrycount > 0)
     {
       fnotice (stderr, "%s:%d: confused by earlier errors, bailing out\n",
-	       input_filename, lineno);
+	       input_filename, input_line);
       exit (FATAL_EXIT_CODE);
     }
 #endif
@@ -1185,7 +1185,7 @@ internal_error VPARAMS ((const char *msgid, ...))
   if (global_dc->internal_error != 0)
     (*global_dc->internal_error) (_(msgid), &ap);
 
-  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, input_line,
                        DK_ICE);
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
@@ -1236,7 +1236,7 @@ warning VPARAMS ((const char *msgid, ...))
   VA_OPEN (ap, msgid);
   VA_FIXEDARG (ap, const char *, msgid);
 
-  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, input_line,
                        DK_WARNING);
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
@@ -1382,10 +1382,12 @@ diagnostic_report_current_module (context)
       for (p = input_file_stack->next; p; p = p->next)
 	if (p == input_file_stack->next)
 	  output_verbatim (&context->buffer,
-                           "In file included from %s:%d", p->name, p->line);
+                           "In file included from %s:%d",
+			   p->name, p->line);
 	else
 	  output_verbatim (&context->buffer,
-                           ",\n                 from %s:%d", p->name, p->line);
+                           ",\n                 from %s:%d",
+			   p->name, p->line);
       output_verbatim (&context->buffer, ":\n");
       diagnostic_set_last_module (context);
     }
@@ -1416,7 +1418,7 @@ inform VPARAMS ((const char *msgid, ...))
   VA_OPEN (ap, msgid);
   VA_FIXEDARG (ap, const char *, msgid);
 
-  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, lineno,
+  diagnostic_set_info (&diagnostic, msgid, &ap, input_filename, input_line,
                        DK_NOTE);
   report_diagnostic (&diagnostic);
   VA_CLOSE (ap);
diff --git a/gcc/expr.c b/gcc/expr.c
index 6f0b36cfadacbabfebfe2417529ae05928e46d89..cbd481175020cc980522f8a0821aab4406879488 100644
--- a/gcc/expr.c
+++ b/gcc/expr.c
@@ -6933,15 +6933,15 @@ expand_expr (exp, target, tmode, modifier)
       {
 	rtx to_return;
 	const char *saved_input_filename = input_filename;
-	int saved_lineno = lineno;
+	int saved_lineno = input_line;
 	input_filename = EXPR_WFL_FILENAME (exp);
-	lineno = EXPR_WFL_LINENO (exp);
+	input_line = EXPR_WFL_LINENO (exp);
 	if (EXPR_WFL_EMIT_LINE_NOTE (exp))
-	  emit_line_note (input_filename, lineno);
+	  emit_line_note (input_filename, input_line);
 	/* Possibly avoid switching back and forth here.  */
 	to_return = expand_expr (EXPR_WFL_NODE (exp), target, tmode, modifier);
 	input_filename = saved_input_filename;
-	lineno = saved_lineno;
+	input_line = saved_lineno;
 	return to_return;
       }
 
diff --git a/gcc/f/ChangeLog b/gcc/f/ChangeLog
index 08537f6765e229778ab0b65c8301eb3d227caae0..a1c16a51d2e7021498cd212db7ae344188677f42 100644
--- a/gcc/f/ChangeLog
+++ b/gcc/f/ChangeLog
@@ -1,5 +1,19 @@
 2003-05-01  Nathan Sidwell  <nathan@codesourcery.com>
 
+	* ansify.c (die_unless): Rename lineno to input_line.
+	* com.c (ffecom_subscript_check_, ffecom_do_entry_,
+	ffecom_gen_sfuncdef_, ffecom_start_progunit_,
+	ffecom_sym_transform_, ffecom_sym_transform_assign_,
+	bison_rule_pushlevel_, bison_rule_compstmt_, finish_function,
+	store_parm_decls): Likewise.
+	* intrin.c (ffeintrin_fulfill_generic): Likewise.
+	* lex.c (ffelex_hash_, ffelex_include_, ffelex_next_line_,
+	ffelex_file_fixed, ffelex_file_free): Likewise.
+	* std.c (ffestd_exec_end): Likewise.
+	* ste.c (ffeste_emit_line_note_, ffeste_start_block_,
+	ffeste_start_stmt_): Likewise.
+	* ste.h (ffeste_filelinenum, ffeste_set_line): Likewise.
+
 	* lex.c (ffelex_file_pop_): Rename parameter from input_filename.
 	(ffelex_file_push_): Likewise.
 	
diff --git a/gcc/f/ansify.c b/gcc/f/ansify.c
index 84efb9664f34ae4bf5f77977fe24dacad62945f4..fa29dfc674fb052035d7c72833e26156255645ad 100644
--- a/gcc/f/ansify.c
+++ b/gcc/f/ansify.c
@@ -1,5 +1,5 @@
 /* ansify.c
-   Copyright (C) 1997 Free Software Foundation, Inc.
+   Copyright (C) 1997, 2003 Free Software Foundation, Inc.
    Contributed by James Craig Burley.
 
 This file is part of GNU Fortran.
@@ -27,7 +27,7 @@ the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #define die_unless(c) \
   do if (!(c)) \
     { \
-      fprintf (stderr, "%s:%lu: %s\n", argv[1], lineno, #c); \
+      fprintf (stderr, "%s:%lu: %s\n", argv[1], input_line, #c); \
       die (); \
     } \
   while(0)
diff --git a/gcc/f/com.c b/gcc/f/com.c
index c92786bb120a11a2d6355b1bcc335052c354d491..a84f8076032d1d0def09e6507b20dd228ab1a4a6 100644
--- a/gcc/f/com.c
+++ b/gcc/f/com.c
@@ -791,7 +791,7 @@ ffecom_subscript_check_ (tree array, tree element, int dim, int total_dims,
 		     arg3);
 
     arg4 = convert (ffecom_f2c_ftnint_type_node,
-		    build_int_2 (lineno, 0));
+		    build_int_2 (input_line, 0));
 
     arg1 = build_tree_list (NULL_TREE, arg1);
     arg2 = build_tree_list (NULL_TREE, arg2);
@@ -2583,11 +2583,11 @@ ffecom_do_entry_ (ffesymbol fn, int entrynum)
   bool cmplxfunc;		/* Use f2c way of returning COMPLEX. */
   bool multi;			/* Master fn has multiple return types. */
   bool altreturning = FALSE;	/* This entry point has alternate returns. */
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   input_filename = ffesymbol_where_filename (fn);
-  lineno = ffesymbol_where_filelinenum (fn);
+  input_line = ffesymbol_where_filelinenum (fn);
 
   ffecom_doing_entry_ = TRUE;	/* Don't bother with array dimensions. */
 
@@ -2917,7 +2917,7 @@ ffecom_do_entry_ (ffesymbol fn, int entrynum)
 
   finish_function (0);
 
-  lineno = old_lineno;
+  input_line = old_lineno;
   input_filename = old_input_filename;
 
   ffecom_doing_entry_ = FALSE;
@@ -6110,7 +6110,7 @@ ffecom_gen_sfuncdef_ (ffesymbol s, ffeinfoBasictype bt, ffeinfoKindtype kt)
   tree result;
   bool charfunc = (bt == FFEINFO_basictypeCHARACTER);
   static bool recurse = FALSE;
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   ffecom_nested_entry_ = s;
@@ -6124,7 +6124,7 @@ ffecom_gen_sfuncdef_ (ffesymbol s, ffeinfoBasictype bt, ffeinfoKindtype kt)
      see how it works at this point.  */
 
   input_filename = ffesymbol_where_filename (s);
-  lineno = ffesymbol_where_filelinenum (s);
+  input_line = ffesymbol_where_filelinenum (s);
 
   /* Pretransform the expression so any newly discovered things belong to the
      outer program unit, not to the statement function. */
@@ -6221,7 +6221,7 @@ ffecom_gen_sfuncdef_ (ffesymbol s, ffeinfoBasictype bt, ffeinfoKindtype kt)
 
   recurse = FALSE;
 
-  lineno = old_lineno;
+  input_line = old_lineno;
   input_filename = old_input_filename;
 
   ffecom_nested_entry_ = NULL;
@@ -7080,14 +7080,14 @@ ffecom_start_progunit_ ()
   && (ffecom_primary_entry_kind_ == FFEINFO_kindFUNCTION)
   && (ffecom_master_bt_ == FFEINFO_basictypeNONE);
   bool main_program = FALSE;
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   assert (fn != NULL);
   assert (ffesymbol_hook (fn).decl_tree == NULL_TREE);
 
   input_filename = ffesymbol_where_filename (fn);
-  lineno = ffesymbol_where_filelinenum (fn);
+  input_line = ffesymbol_where_filelinenum (fn);
 
   switch (ffecom_primary_entry_kind_)
     {
@@ -7269,7 +7269,7 @@ ffecom_start_progunit_ ()
   /* Disallow temp vars at this level.  */
   current_binding_level->prep_state = 2;
 
-  lineno = old_lineno;
+  input_line = old_lineno;
   input_filename = old_input_filename;
 
   /* This handles any symbols still untransformed, in case -g specified.
@@ -7298,7 +7298,7 @@ ffecom_sym_transform_ (ffesymbol s)
   ffeinfoBasictype bt;
   ffeinfoKindtype kt;
   ffeglobal g;
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   /* Must ensure special ASSIGN variables are declared at top of outermost
@@ -7318,14 +7318,14 @@ ffecom_sym_transform_ (ffesymbol s)
   if (ffesymbol_sfdummyparent (s) == NULL)
     {
       input_filename = ffesymbol_where_filename (s);
-      lineno = ffesymbol_where_filelinenum (s);
+      input_line = ffesymbol_where_filelinenum (s);
     }
   else
     {
       ffesymbol sf = ffesymbol_sfdummyparent (s);
 
       input_filename = ffesymbol_where_filename (sf);
-      lineno = ffesymbol_where_filelinenum (sf);
+      input_line = ffesymbol_where_filelinenum (sf);
     }
 
   bt = ffeinfo_basictype (ffebld_info (s));
@@ -8294,7 +8294,7 @@ ffecom_sym_transform_ (ffesymbol s)
   ffesymbol_hook (s).length_tree = tlen;
   ffesymbol_hook (s).addr = addr;
 
-  lineno = old_lineno;
+  input_line = old_lineno;
   input_filename = old_input_filename;
 
   return s;
@@ -8312,20 +8312,20 @@ static ffesymbol
 ffecom_sym_transform_assign_ (ffesymbol s)
 {
   tree t;			/* Transformed thingy. */
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   if (ffesymbol_sfdummyparent (s) == NULL)
     {
       input_filename = ffesymbol_where_filename (s);
-      lineno = ffesymbol_where_filelinenum (s);
+      input_line = ffesymbol_where_filelinenum (s);
     }
   else
     {
       ffesymbol sf = ffesymbol_sfdummyparent (s);
 
       input_filename = ffesymbol_where_filename (sf);
-      lineno = ffesymbol_where_filelinenum (sf);
+      input_line = ffesymbol_where_filelinenum (sf);
     }
 
   assert (!ffecom_transform_only_dummies_);
@@ -8375,7 +8375,7 @@ ffecom_sym_transform_assign_ (ffesymbol s)
 
   ffesymbol_hook (s).assign_tree = t;
 
-  lineno = old_lineno;
+  input_line = old_lineno;
   input_filename = old_input_filename;
 
   return s;
@@ -13115,7 +13115,7 @@ ffecom_which_entrypoint_decl ()
 static void
 bison_rule_pushlevel_ ()
 {
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   pushlevel (0);
   clear_last_expr ();
   expand_start_bindings (0);
@@ -13131,7 +13131,7 @@ bison_rule_compstmt_ ()
   if (! keep)
     current_binding_level->names = NULL_TREE;
 
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
   expand_end_bindings (getdecls (), keep, 0);
   t = poplevel (keep, 1, 0);
 
@@ -13585,7 +13585,7 @@ finish_function (int nested)
 
       /* Obey `register' declarations if `setjmp' is called in this fn.  */
       /* Generate rtl for function exit.  */
-      expand_function_end (input_filename, lineno, 0);
+      expand_function_end (input_filename, input_line, 0);
 
       /* If this is a nested function, protect the local variables in the stack
 	 above us from being collected while we're compiling this function.  */
@@ -13866,7 +13866,7 @@ store_parm_decls (int is_main_program UNUSED)
 
   /* Initialize the RTL code for the function.  */
 
-  init_function_start (fndecl, input_filename, lineno);
+  init_function_start (fndecl, input_filename, input_line);
 
   /* Set up parameters and prepare for return, for the function.  */
 
diff --git a/gcc/f/intrin.c b/gcc/f/intrin.c
index 1c6c00c732108adb1b6093ee987831c14ba1b499..cc100bf9e51fb4951e48c05b69ac2afbc68abd69 100644
--- a/gcc/f/intrin.c
+++ b/gcc/f/intrin.c
@@ -1,5 +1,6 @@
 /* intrin.c -- Recognize references to intrinsics
-   Copyright (C) 1995, 1996, 1997, 1998, 2002 Free Software Foundation, Inc.
+   Copyright (C) 1995, 1996, 1997, 1998, 2002,
+   2003 Free Software Foundation, Inc.
    Contributed by James Craig Burley.
 
 This file is part of GNU Fortran.
@@ -1389,7 +1390,7 @@ ffeintrin_fulfill_generic (ffebld *expr, ffeinfo *info, ffelexToken t)
       if (!highly_specific && (nimp != FFEINTRIN_impNONE))
 	{
 	  fprintf (stderr, "lineno=%ld, gen=%s, imp=%s, timp=%s\n",
-		   (long) lineno,
+		   (long) input_line,
 		   ffeintrin_gens_[gen].name,
 		   ffeintrin_imps_[imp].name,
 		   ffeintrin_imps_[nimp].name);
diff --git a/gcc/f/lex.c b/gcc/f/lex.c
index 3e8465d76c4914fc170fedcfae64b3e8cb62065f..f1e2e97cd55a40287b3c8fda8a69ff0ee7cb52db 100644
--- a/gcc/f/lex.c
+++ b/gcc/f/lex.c
@@ -1,5 +1,5 @@
 /* Implementation of Fortran lexer
-   Copyright (C) 1995, 1996, 1997, 1998, 2001, 2002
+   Copyright (C) 1995, 1996, 1997, 1998, 2001, 2002, 2003
    Free Software Foundation, Inc.
    Contributed by James Craig Burley.
 
@@ -1096,7 +1096,7 @@ ffelex_hash_ (FILE *finput)
 	      c = ffelex_get_directive_line_ (&text, finput);
 
 	      if (debug_info_level == DINFO_LEVEL_VERBOSE)
-		(*debug_hooks->define) (lineno, text);
+		(*debug_hooks->define) (input_line, text);
 
 	      goto skipline;
 	    }
@@ -1115,7 +1115,7 @@ ffelex_hash_ (FILE *finput)
 	      c = ffelex_get_directive_line_ (&text, finput);
 
 	      if (debug_info_level == DINFO_LEVEL_VERBOSE)
-		(*debug_hooks->undef) (lineno, text);
+		(*debug_hooks->undef) (input_line, text);
 
 	      goto skipline;
 	    }
@@ -1193,7 +1193,7 @@ ffelex_hash_ (FILE *finput)
   if ((token != NULL)
       && (ffelex_token_type (token) == FFELEX_typeNUMBER))
     {
-      int old_lineno = lineno;
+      int old_lineno = input_line;
       const char *old_input_filename = input_filename;
       ffewhereFile wf;
 
@@ -1207,7 +1207,7 @@ ffelex_hash_ (FILE *finput)
       if (c == '\n' || c == EOF)
 	{
 	  /* No more: store the line number and check following line.  */
-	  lineno = l;
+	  input_line = l;
 	  if (!ffelex_kludge_flag_)
 	    {
 	      ffewhere_file_set (NULL, TRUE, (ffewhereLineNumber) l);
@@ -1230,7 +1230,7 @@ ffelex_hash_ (FILE *finput)
 	  goto skipline;
 	}
 
-      lineno = l;
+      input_line = l;
 
       if (ffelex_kludge_flag_)
 	input_filename = ggc_strdup (ffelex_token_text (token));
@@ -1280,7 +1280,7 @@ ffelex_hash_ (FILE *finput)
 
 	  if (ffelex_kludge_flag_)
 	    {
-	      lineno = 1;
+	      input_line = 1;
 	      input_filename = old_input_filename;
 	      error ("use `#line ...' instead of `# ...' in first line");
 	    }
@@ -1324,7 +1324,7 @@ ffelex_hash_ (FILE *finput)
 	   || (c != '\n' && c != EOF))
 	  && ffelex_kludge_flag_)
 	{
-	  lineno = 1;
+	  input_line = 1;
 	  input_filename = old_input_filename;
 	  error ("use `#line ...' instead of `# ...' in first line");
 	}
@@ -1470,7 +1470,7 @@ ffelex_include_ ()
   ffewhereLineNumber linecount_current = ffelex_linecount_current_;
   ffewhereLineNumber linecount_offset
     = ffewhere_line_filelinenum (current_wl);
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   if (card_length != 0)
@@ -1513,7 +1513,7 @@ ffelex_include_ ()
   ffelex_card_image_[card_length] = '\0';
 
   input_filename = old_input_filename;
-  lineno = old_lineno;
+  input_line = old_lineno;
   ffelex_linecount_current_ = linecount_current;
   ffelex_current_wf_ = current_wf;
   ffelex_final_nontab_column_ = final_nontab_column;
@@ -1571,7 +1571,7 @@ ffelex_next_line_ ()
 {
   ffelex_linecount_current_ = ffelex_linecount_next_;
   ++ffelex_linecount_next_;
-  ++lineno;
+  ++input_line;
 }
 
 static void
@@ -1787,7 +1787,7 @@ ffelex_file_fixed (ffewhereFile wf, FILE *f)
 
   assert (ffelex_handler_ != NULL);
 
-  lineno = 0;
+  input_line = 0;
   input_filename = ffewhere_file_name (wf);
   ffelex_current_wf_ = wf;
   disallow_continuation_line = TRUE;
@@ -2977,7 +2977,7 @@ ffelex_file_free (ffewhereFile wf, FILE *f)
 
   assert (ffelex_handler_ != NULL);
 
-  lineno = 0;
+  input_line = 0;
   input_filename = ffewhere_file_name (wf);
   ffelex_current_wf_ = wf;
   continuation_line = FALSE;
diff --git a/gcc/f/std.c b/gcc/f/std.c
index c9ff189b79677fe7b523c515bf8b77775ad64ccb..439ae887c3871ea833b29b810224d8977ccb6367 100644
--- a/gcc/f/std.c
+++ b/gcc/f/std.c
@@ -1,5 +1,5 @@
 /* std.c -- Implementation File (module.c template V1.0)
-   Copyright (C) 1995, 1996, 2000, 2002 Free Software Foundation, Inc.
+   Copyright (C) 1995, 1996, 2000, 2002, 2003 Free Software Foundation, Inc.
    Contributed by James Craig Burley.
 
 This file is part of GNU Fortran.
@@ -1423,7 +1423,7 @@ ffestd_exec_begin ()
 void
 ffestd_exec_end ()
 {
-  int old_lineno = lineno;
+  int old_lineno = input_line;
   const char *old_input_filename = input_filename;
 
   ffecom_end_transition ();
@@ -1456,7 +1456,7 @@ ffestd_exec_end ()
   ffestd_stmt_list_.last = NULL;
   ffestd_2pass_entrypoints_ = 0;
 
-  lineno = old_lineno;
+  input_line = old_lineno;
   input_filename = old_input_filename;
 }
 
diff --git a/gcc/f/ste.c b/gcc/f/ste.c
index ed94ae35174adecbc80dc57e9a9ce448f910118a..1648d8fef9b2813d434a4d623c51743623953ae3 100644
--- a/gcc/f/ste.c
+++ b/gcc/f/ste.c
@@ -141,7 +141,7 @@ static void ffeste_subr_beru_ (ffestpBeruStmt *info, ffecomGfrt rt);
 /* Internal macros. */
 
 #define ffeste_emit_line_note_() \
-  emit_line_note (input_filename, lineno)
+  emit_line_note (input_filename, input_line)
 #define ffeste_check_simple_() \
   assert(ffeste_statelet_ == FFESTE_stateletSIMPLE_)
 #define ffeste_check_start_() \
@@ -401,7 +401,7 @@ ffeste_start_block_ (ffestw block)
 
   b->outer = ffeste_top_block_;
   b->block = block;
-  b->lineno = lineno;
+  b->lineno = input_line;
   b->filename = input_filename;
   b->is_stmt = FALSE;
 
@@ -443,7 +443,7 @@ ffeste_start_stmt_(void)
 
   b->outer = ffeste_top_block_;
   b->block = NULL;
-  b->lineno = lineno;
+  b->lineno = input_line;
   b->filename = input_filename;
   b->is_stmt = TRUE;
 
diff --git a/gcc/f/ste.h b/gcc/f/ste.h
index fb32c792f9801cee7908324522d7f792c297a651..d911105559d9dbcecec85bd78937e707bf569903 100644
--- a/gcc/f/ste.h
+++ b/gcc/f/ste.h
@@ -1,5 +1,5 @@
 /* ste.h -- Private #include File (module.h template V1.0)
-   Copyright (C) 1995 Free Software Foundation, Inc.
+   Copyright (C) 1995, 2003 Free Software Foundation, Inc.
    Contributed by James Craig Burley.
 
 This file is part of GNU Fortran.
@@ -148,9 +148,9 @@ void ffeste_V026 (ffestpFindStmt *info);
 #define ffeste_init_3()
 #define ffeste_init_4()
 #define ffeste_filename() input_filename
-#define ffeste_filelinenum() lineno
+#define ffeste_filelinenum() input_line
 #define ffeste_set_line(name,num) \
-  (input_filename = (name), lineno = (num))
+  (input_filename = (name), input_line = (num))
 #define ffeste_terminate_0()
 #define ffeste_terminate_1()
 #ifdef ENABLE_CHECKING
diff --git a/gcc/input.h b/gcc/input.h
index 28bb64818324b1e265b2e0acf5a5a62e2b4c3294..0bc15dea45fbdfe40d01be2c462e7cd5f6f26073 100644
--- a/gcc/input.h
+++ b/gcc/input.h
@@ -1,6 +1,6 @@
 /* Declarations for variables relating to reading the source file.
    Used by parsers, lexical analyzers, and error message routines.
-   Copyright (C) 1993, 1997, 1998, 2000 Free Software Foundation, Inc.
+   Copyright (C) 1993, 1997, 1998, 2000, 2003 Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -26,7 +26,7 @@ extern const char *input_filename;
 extern const char *main_input_filename;
 
 /* Line number in current source file.  */
-extern int lineno;
+extern int input_line;
 
 /* Stream for reading from input file.  */
 extern FILE *finput;
diff --git a/gcc/integrate.c b/gcc/integrate.c
index 60fa2acd13a6609688be8bb9bf531a42099084ad..3e7f94b4691c16a843eb8e71624a919b4c40cde3 100644
--- a/gcc/integrate.c
+++ b/gcc/integrate.c
@@ -1307,7 +1307,7 @@ expand_inline_function (fndecl, parms, target, ignore, type,
   if (flag_test_coverage)
     emit_note (0, NOTE_INSN_REPEATED_LINE_NUMBER);
 
-  emit_line_note (input_filename, lineno);
+  emit_line_note (input_filename, input_line);
 
   /* If the function returns a BLKmode object in a register, copy it
      out of the temp register into a BLKmode memory object.  */
@@ -3041,7 +3041,7 @@ output_inline_function (fndecl)
   /* Make sure warnings emitted by the optimizers (e.g. control reaches
      end of non-void function) is not wildly incorrect.  */
   input_filename = DECL_SOURCE_FILE (fndecl);
-  lineno = DECL_SOURCE_LINE (fndecl);
+  input_line = DECL_SOURCE_LINE (fndecl);
 
   /* Compile this function all the way down to assembly code.  As a
      side effect this destroys the saved RTL representation, but
diff --git a/gcc/java/check-init.c b/gcc/java/check-init.c
index 3ca989b424bab85ff79a604916c394412964f453..82b14b57cfc86c164ff4ddc15864ebbe8e532eb1 100644
--- a/gcc/java/check-init.c
+++ b/gcc/java/check-init.c
@@ -890,15 +890,15 @@ check_init (tree exp, words before)
 	const char *saved_input_filename = input_filename;
 	tree saved_wfl = wfl;
 	tree body = EXPR_WFL_NODE (exp);
-	int saved_lineno = lineno;
+	int saved_lineno = input_line;
 	if (body == empty_stmt_node)
 	  break;
 	wfl = exp;
 	input_filename = EXPR_WFL_FILENAME (exp);
-	lineno = EXPR_WFL_LINENO (exp);
+	input_line = EXPR_WFL_LINENO (exp);
 	check_init (body, before);
 	input_filename = saved_input_filename;
-	lineno = saved_lineno;
+	input_line = saved_lineno;
 	wfl = saved_wfl;
       }
       break;
diff --git a/gcc/java/class.c b/gcc/java/class.c
index fff42473cd06dce1c10d1f858488eb048083f9f1..e51e79996c3109331191a933ec687caf3563fcb5 100644
--- a/gcc/java/class.c
+++ b/gcc/java/class.c
@@ -309,18 +309,18 @@ push_class (tree class_type, tree class_name)
 {
   tree decl, signature;
   const char *save_input_filename = input_filename;
-  int save_lineno = lineno;
+  int save_lineno = input_line;
   tree source_name = identifier_subst (class_name, "", '.', '/', ".java");
   CLASS_P (class_type) = 1;
   input_filename = IDENTIFIER_POINTER (source_name);
-  lineno = 0;
+  input_line = 0;
   decl = build_decl (TYPE_DECL, class_name, class_type);
 
   /* dbxout needs a DECL_SIZE if in gstabs mode */
   DECL_SIZE (decl) = integer_zero_node;
 
   input_filename = save_input_filename;
-  lineno = save_lineno;
+  input_line = save_lineno;
   signature = identifier_subst (class_name, "L", '.', '/', ";");
   IDENTIFIER_SIGNATURE_TYPE (signature) = build_pointer_type (class_type);
 
diff --git a/gcc/java/decl.c b/gcc/java/decl.c
index 70d6e5980f919671f341cf779eb412e8218efb47..a4b1c43fd609edca5ed1a169dba743e5c4a49f11 100644
--- a/gcc/java/decl.c
+++ b/gcc/java/decl.c
@@ -1670,7 +1670,7 @@ complete_start_java_method (tree fndecl)
   if (! flag_emit_class_files)
     {
       /* Initialize the RTL code for the function.  */
-      init_function_start (fndecl, input_filename, lineno);
+      init_function_start (fndecl, input_filename, input_line);
 
       /* Set up parameters and prepare for return, for the function.  */
       expand_function_start (fndecl, 0);
@@ -1810,7 +1810,7 @@ end_java_method (void)
   BLOCK_SUPERCONTEXT (DECL_INITIAL (fndecl)) = fndecl;
 
   /* Generate rtl for function exit.  */
-  expand_function_end (input_filename, lineno, 0);
+  expand_function_end (input_filename, input_line, 0);
 
   /* Run the optimizers and output assembler code for this function. */
   rest_of_compilation (fndecl);
diff --git a/gcc/java/expr.c b/gcc/java/expr.c
index 11748238fd751c37e29ee790d32d4d464413109b..6cbfbc9f19f8f541deb64dd462d0f9ec85e364cb 100644
--- a/gcc/java/expr.c
+++ b/gcc/java/expr.c
@@ -2827,8 +2827,8 @@ expand_byte_code (JCF *jcf, tree method)
 	      linenumber_pointer += 4;
 	      if (pc == PC)
 		{
-		  lineno = GET_u2 (linenumber_pointer - 2);
-		  emit_line_note (input_filename, lineno);
+		  input_line = GET_u2 (linenumber_pointer - 2);
+		  emit_line_note (input_filename, input_line);
 		  if (!(instruction_bits[PC] & BCODE_HAS_MULTI_LINENUMBERS))
 		    break;
 		}
diff --git a/gcc/java/jcf-parse.c b/gcc/java/jcf-parse.c
index 8daceccf4dd17e6919d23f8c200637ea0751f5e4..d642bdccb752ebe7e6e0f131ec475dfb1fe1aa0b 100644
--- a/gcc/java/jcf-parse.c
+++ b/gcc/java/jcf-parse.c
@@ -418,7 +418,7 @@ give_name_to_class (JCF *jcf, int i)
 					    JPOOL_UTF_LENGTH (jcf, j));
       this_class = lookup_class (class_name);
       input_filename = DECL_SOURCE_FILE (TYPE_NAME (this_class));
-      lineno = 0;
+      input_line = 0;
       if (main_input_filename == NULL && jcf == main_jcf)
 	main_input_filename = input_filename;
 
@@ -703,13 +703,13 @@ parse_class_file (void)
 {
   tree method, field;
   const char *save_input_filename = input_filename;
-  int save_lineno = lineno;
+  int save_lineno = input_line;
 
   java_layout_seen_class_methods ();
 
   input_filename = DECL_SOURCE_FILE (TYPE_NAME (current_class));
-  lineno = 0;
-  (*debug_hooks->start_source_file) (lineno, input_filename);
+  input_line = 0;
+  (*debug_hooks->start_source_file) (input_line, input_filename);
   init_outgoing_cpool ();
 
   /* Currently we always have to emit calls to _Jv_InitClass when
@@ -760,7 +760,7 @@ parse_class_file (void)
 	  continue;
 	}
 
-      lineno = 0;
+      input_line = 0;
       if (DECL_LINENUMBERS_OFFSET (method))
 	{
 	  register int i;
@@ -774,8 +774,8 @@ parse_class_file (void)
 	      int line = GET_u2 (ptr);
 	      /* Set initial lineno lineno to smallest linenumber.
 	       * Needs to be set before init_function_start. */
-	      if (lineno == 0 || line < lineno)
-		lineno = line;
+	      if (input_line == 0 || line < input_line)
+		input_line = line;
 	    }  
 	}
       else
@@ -803,7 +803,7 @@ parse_class_file (void)
 
   (*debug_hooks->end_source_file) (save_lineno);
   input_filename = save_input_filename;
-  lineno = save_lineno;
+  input_line = save_lineno;
 }
 
 /* Parse a source file, as pointed by the current value of INPUT_FILENAME. */
diff --git a/gcc/java/jcf-write.c b/gcc/java/jcf-write.c
index 9c05a5ae831c3d1ff72b784bef21ea8c5f3aa25c..59ef514edb41af3311fdc2c1ba566c293ee25d5a 100644
--- a/gcc/java/jcf-write.c
+++ b/gcc/java/jcf-write.c
@@ -1425,17 +1425,17 @@ generate_bytecode_insns (tree exp, int target, struct jcf_partial *state)
       {
 	const char *saved_input_filename = input_filename;
 	tree body = EXPR_WFL_NODE (exp);
-	int saved_lineno = lineno;
+	int saved_lineno = input_line;
 	if (body == empty_stmt_node)
 	  break;
 	input_filename = EXPR_WFL_FILENAME (exp);
-	lineno = EXPR_WFL_LINENO (exp);
-	if (EXPR_WFL_EMIT_LINE_NOTE (exp) && lineno > 0
+	input_line = EXPR_WFL_LINENO (exp);
+	if (EXPR_WFL_EMIT_LINE_NOTE (exp) && input_line > 0
 	    && debug_info_level > DINFO_LEVEL_NONE)
-	  put_linenumber (lineno, state);
+	  put_linenumber (input_line, state);
 	generate_bytecode_insns (body, target, state);
 	input_filename = saved_input_filename;
-	lineno = saved_lineno;
+	input_line = saved_lineno;
       }
       break;
     case INTEGER_CST:
diff --git a/gcc/java/lex.c b/gcc/java/lex.c
index d18aa1b9954f39de5f8f0a6edc4a82a70577996b..e21bfd649af9ccc83dd3bc01962847b5525b159c 100644
--- a/gcc/java/lex.c
+++ b/gcc/java/lex.c
@@ -135,7 +135,7 @@ java_init_lex (FILE *finput, const char *encoding)
 #endif
 
   ctxp->filename = input_filename;
-  ctxp->lineno = lineno = 0;
+  ctxp->lineno = input_line = 0;
   ctxp->p_line = NULL;
   ctxp->c_line = NULL;
   ctxp->java_error_flag = 0;
@@ -212,7 +212,7 @@ java_allocate_new_line (void)
     }
   ctxp->c_line->ahead [0] = 0;
   ctxp->c_line->unicode_escape_ahead_p = 0;
-  ctxp->c_line->lineno = ++lineno;
+  ctxp->c_line->lineno = ++input_line;
   ctxp->c_line->white_space_only = 1;
 }
 
@@ -1351,9 +1351,9 @@ do_java_lex (YYSTYPE *java_lval)
 	}
       if (c == '\n' || c == UEOF) /* ULT.  */
 	{
-	  lineno--;	/* Refer to the line where the terminator was seen.  */
+	  input_line--;	/* Refer to the line where the terminator was seen.  */
 	  java_lex_error ("String not terminated at end of line", 0);
-	  lineno++;
+	  input_line++;
 	}
 
       obstack_1grow (&temporary_obstack, '\0');
@@ -1381,14 +1381,14 @@ do_java_lex (YYSTYPE *java_lval)
     case '{':
       JAVA_LEX_SEP (c);
       if (ctxp->ccb_indent == 1)
-	ctxp->first_ccb_indent1 = lineno;
+	ctxp->first_ccb_indent1 = input_line;
       ctxp->ccb_indent++;
       BUILD_OPERATOR (OCB_TK);
     case '}':
       JAVA_LEX_SEP (c);
       ctxp->ccb_indent--;
       if (ctxp->ccb_indent == 1)
-        ctxp->last_ccb_indent1 = lineno;
+        ctxp->last_ccb_indent1 = input_line;
       BUILD_OPERATOR (CCB_TK);
     case '[':
       JAVA_LEX_SEP (c);
diff --git a/gcc/java/lex.h b/gcc/java/lex.h
index aa9a2beea34ae1357ba4664cd43ac58023a343d1..3c924e4e4a5ca34a4ec8cf68dfe1f77ec299201e 100644
--- a/gcc/java/lex.h
+++ b/gcc/java/lex.h
@@ -29,7 +29,7 @@ The Free Software Foundation is independent of Sun Microsystems, Inc.  */
 
 /* Extern global variables declarations  */
 extern FILE *finput;
-extern int   lineno;
+extern int   input_lineno;
 
 /* A Unicode character, as read from the input file  */
 typedef unsigned short unicode_t;
diff --git a/gcc/java/parse-scan.y b/gcc/java/parse-scan.y
index 0c8795f2b1d414cce5346baf1df5e0d330a609a4..233a98707c4f8843087fd70f7b6dbe29d4fa937a 100644
--- a/gcc/java/parse-scan.y
+++ b/gcc/java/parse-scan.y
@@ -58,7 +58,7 @@ static struct parser_ctxt *ctxp;
    elsewhere  */
 int java_error_count;
 int java_warning_count;
-int lineno;
+int input_line;
 
 /* Tweak default rules when necessary.  */
 static int absorber;
@@ -1354,6 +1354,6 @@ void reset_report (void)
 void
 yyerror (const char *msg ATTRIBUTE_UNUSED)
 {
-  fprintf (stderr, "%s: %d: %s\n", input_filename, lineno, msg);
+  fprintf (stderr, "%s: %d: %s\n", input_filename, input_line, msg);
   exit (1);
 }
diff --git a/gcc/java/parse.h b/gcc/java/parse.h
index 17806dc21a89a367b4f7ce532e9fe07cd1a5f9a0..207bb8d8bf3c4e6457d0637eb401963537857de4 100644
--- a/gcc/java/parse.h
+++ b/gcc/java/parse.h
@@ -70,7 +70,7 @@ extern tree stabilize_reference (tree);
 #define RECOVER     {yyerrok; RECOVERED;}
 
 #define YYERROR_NOW ctxp->java_error_flag = 1
-#define YYNOT_TWICE if (ctxp->prevent_ese != lineno)
+#define YYNOT_TWICE if (ctxp->prevent_ese != input_line)
 
 /* Accepted modifiers */
 #define CLASS_MODIFIERS ACC_PUBLIC|ACC_ABSTRACT|ACC_FINAL|ACC_STRICT
diff --git a/gcc/java/parse.y b/gcc/java/parse.y
index df60f9e221065270a698a069c4b6cd5fde4e3885..c35d4e504aaa66bc7ad2549ee5d449b1e3efaaf7 100644
--- a/gcc/java/parse.y
+++ b/gcc/java/parse.y
@@ -1452,7 +1452,7 @@ empty_statement:
 			   (DECL_CONTEXT (current_function_decl)))))
 
 		    {
-		      EXPR_WFL_SET_LINECOL (wfl_operator, lineno, -1);
+		      EXPR_WFL_SET_LINECOL (wfl_operator, input_line, -1);
 		      parse_warning_context (wfl_operator, "An empty declaration is a deprecated feature that should not be used");
 		    }
 		  $$ = empty_stmt_node;
@@ -1489,7 +1489,7 @@ expression_statement:
 		{
 		  /* We have a statement. Generate a WFL around it so
 		     we can debug it */
-		  $$ = build_expr_wfl ($1, input_filename, lineno, 0);
+		  $$ = build_expr_wfl ($1, input_filename, input_line, 0);
 		  /* We know we have a statement, so set the debug
                      info to be eventually generate here. */
 		  $$ = JAVA_MAYBE_GENERATE_DEBUG_INFO ($$);
@@ -2692,7 +2692,7 @@ java_pop_parser_context (int generate)
   next = ctxp->next;
   if (next)
     {
-      lineno = ctxp->lineno;
+      input_line = ctxp->lineno;
       current_class = ctxp->class_type;
     }
 
@@ -2737,7 +2737,7 @@ java_parser_context_save_global (void)
   else if (ctxp->saved_data)
     create_new_parser_context (1);
 
-  ctxp->lineno = lineno;
+  ctxp->lineno = input_line;
   ctxp->class_type = current_class;
   ctxp->filename = input_filename;
   ctxp->function_decl = current_function_decl;
@@ -2750,7 +2750,7 @@ java_parser_context_save_global (void)
 void
 java_parser_context_restore_global (void)
 {
-  lineno = ctxp->lineno;
+  input_line = ctxp->lineno;
   current_class = ctxp->class_type;
   input_filename = ctxp->filename;
   if (wfl_operator)
@@ -2989,7 +2989,7 @@ yyerror (const char *msg)
   int save_lineno;
   char *remainder, *code_from_source;
 
-  if (!force_error && prev_lineno == lineno)
+  if (!force_error && prev_lineno == input_line)
     return;
 
   /* Save current error location but report latter, when the context is
@@ -3022,8 +3022,8 @@ yyerror (const char *msg)
       elc.line = ctxp->p_line->lineno;
     }
 
-  save_lineno = lineno;
-  prev_lineno = lineno = elc.line;
+  save_lineno = input_line;
+  prev_lineno = input_line = elc.line;
   prev_msg = msg;
 
   code_from_source = java_get_line_col (ctxp->filename, elc.line, elc.col);
@@ -3040,7 +3040,7 @@ yyerror (const char *msg)
      the same line. This occurs when we report an error but don't have
      a synchronization point other than ';', which
      expression_statement is the only one to take care of.  */
-  ctxp->prevent_ese = lineno = save_lineno;
+  ctxp->prevent_ese = input_line = save_lineno;
 }
 
 static void
@@ -4225,7 +4225,7 @@ register_fields (int flags, tree type, tree variable_list)
 {
   tree current, saved_type;
   tree class_type = NULL_TREE;
-  int saved_lineno = lineno;
+  int saved_lineno = input_line;
   int must_chain = 0;
   tree wfl = NULL_TREE;
 
@@ -4295,9 +4295,9 @@ register_fields (int flags, tree type, tree variable_list)
       /* Set lineno to the line the field was found and create a
          declaration for it. Eventually sets the @deprecated tag flag. */
       if (flag_emit_xref)
-	lineno = EXPR_WFL_LINECOL (cl);
+	input_line = EXPR_WFL_LINECOL (cl);
       else
-	lineno = EXPR_WFL_LINENO (cl);
+	input_line = EXPR_WFL_LINENO (cl);
       field_decl = add_field (class_type, current_name, real_type, flags);
       CHECK_DEPRECATED_NO_RESET (field_decl);
 
@@ -4359,7 +4359,7 @@ register_fields (int flags, tree type, tree variable_list)
     }
 
   CLEAR_DEPRECATED;
-  lineno = saved_lineno;
+  input_line = saved_lineno;
 }
 
 /* Generate finit$, using the list of initialized fields to populate
@@ -4611,11 +4611,11 @@ method_header (int flags, tree type, tree mdecl, tree throws)
   else
     TREE_TYPE (meth) = type;
 
-  saved_lineno = lineno;
+  saved_lineno = input_line;
   /* When defining an abstract or interface method, the curly
      bracket at level 1 doesn't exist because there is no function
      body */
-  lineno = (ctxp->first_ccb_indent1 ? ctxp->first_ccb_indent1 :
+  input_line = (ctxp->first_ccb_indent1 ? ctxp->first_ccb_indent1 :
 	    EXPR_WFL_LINENO (id));
 
   /* Remember the original argument list */
@@ -4649,7 +4649,7 @@ method_header (int flags, tree type, tree mdecl, tree throws)
   /* Register the parameter number and re-install the current line
      number */
   DECL_MAX_LOCALS (meth) = ctxp->formal_parameter_number+1;
-  lineno = saved_lineno;
+  input_line = saved_lineno;
 
   /* Register exception specified by the `throws' keyword for
      resolution and set the method decl appropriate field to the list.
@@ -5451,13 +5451,13 @@ safe_layout_class (tree class)
 {
   tree save_current_class = current_class;
   const char *save_input_filename = input_filename;
-  int save_lineno = lineno;
+  int save_lineno = input_line;
 
   layout_class (class);
 
   current_class = save_current_class;
   input_filename = save_input_filename;
-  lineno = save_lineno;
+  input_line = save_lineno;
 }
 
 static tree
@@ -6867,7 +6867,7 @@ find_in_imports_on_demand (tree enclosing_type, tree class_type)
 
   for (; import; import = TREE_CHAIN (import))
     {
-      int saved_lineno = lineno;
+      int saved_lineno = input_line;
       int access_check;
       const char *id_name;
       tree decl, type_name_copy;
@@ -6886,7 +6886,7 @@ find_in_imports_on_demand (tree enclosing_type, tree class_type)
 
       /* Setup lineno so that it refers to the line of the import (in
 	 case we parse a class file and encounter errors */
-      lineno = EXPR_WFL_LINENO (TREE_PURPOSE (import));
+      input_line = EXPR_WFL_LINENO (TREE_PURPOSE (import));
 
       type_name_copy = TYPE_NAME (class_type);
       TYPE_NAME (class_type) = node;
@@ -6908,7 +6908,7 @@ find_in_imports_on_demand (tree enclosing_type, tree class_type)
 	/* 6.6.1: Inner classes are subject to member access rules. */
 	access_check = 0;
 
-      lineno = saved_lineno;
+      input_line = saved_lineno;
 
       /* If the loaded class is not accessible or couldn't be loaded,
 	 we restore the original TYPE_NAME and process the next
@@ -7297,7 +7297,7 @@ create_artificial_method (tree class, int flags, tree type,
   tree mdecl;
 
   java_parser_context_save_global ();
-  lineno = 0;
+  input_line = 0;
   mdecl = make_node (FUNCTION_TYPE);
   TREE_TYPE (mdecl) = type;
   TYPE_ARG_TYPES (mdecl) = args;
@@ -7357,7 +7357,7 @@ source_end_java_method (void)
     return;
 
   java_parser_context_save_global ();
-  lineno = ctxp->last_ccb_indent1;
+  input_line = ctxp->last_ccb_indent1;
 
   /* Turn function bodies with only a NOP expr null, so they don't get
      generated at all and we won't get warnings when using the -W
@@ -7385,8 +7385,8 @@ source_end_java_method (void)
   /* Generate rtl for function exit.  */
   if (! flag_emit_class_files && ! flag_emit_xref)
     {
-      lineno = DECL_SOURCE_LINE_LAST (fndecl);
-      expand_function_end (input_filename, lineno, 0);
+      input_line = DECL_SOURCE_LINE_LAST (fndecl);
+      expand_function_end (input_filename, input_line, 0);
 
       DECL_SOURCE_LINE (fndecl) = DECL_SOURCE_LINE_FIRST (fndecl);
 
@@ -7894,7 +7894,7 @@ start_complete_expand_method (tree mdecl)
       TREE_CHAIN (tem) = next;
     }
   pushdecl_force_head (DECL_ARGUMENTS (mdecl));
-  lineno = DECL_SOURCE_LINE_FIRST (mdecl);
+  input_line = DECL_SOURCE_LINE_FIRST (mdecl);
   build_result_decl (mdecl);
 }
 
@@ -8572,7 +8572,7 @@ build_thisn_assign (void)
       tree lhs = make_qualified_primary (build_wfl_node (this_identifier_node),
 					 build_wfl_node (thisn), 0);
       tree rhs = build_wfl_node (thisn);
-      EXPR_WFL_SET_LINECOL (lhs, lineno, 0);
+      EXPR_WFL_SET_LINECOL (lhs, input_line, 0);
       return build_assignment (ASSIGN_TK, EXPR_WFL_LINECOL (lhs), lhs, rhs);
     }
   return NULL_TREE;
@@ -11824,10 +11824,10 @@ java_complete_lhs (tree node)
       else
 	{
 	  tree body;
-	  int save_lineno = lineno;
-	  lineno = EXPR_WFL_LINENO (node);
+	  int save_lineno = input_line;
+	  input_line = EXPR_WFL_LINENO (node);
 	  body = java_complete_tree (EXPR_WFL_NODE (node));
-	  lineno = save_lineno;
+	  input_line = save_lineno;
 	  EXPR_WFL_NODE (node) = body;
 	  TREE_SIDE_EFFECTS (node) = TREE_SIDE_EFFECTS (body);
 	  CAN_COMPLETE_NORMALLY (node) = CAN_COMPLETE_NORMALLY (body);
@@ -12375,7 +12375,7 @@ maybe_absorb_scoping_blocks (void)
     {
       tree b = exit_block ();
       java_method_add_stmt (current_function_decl, b);
-      SOURCE_FRONTEND_DEBUG (("Absorbing scoping block at line %d", lineno));
+      SOURCE_FRONTEND_DEBUG (("Absorbing scoping block at line %d", input_line));
     }
 }
 
diff --git a/gcc/objc/objc-act.c b/gcc/objc/objc-act.c
index 36badee5884d9c34a4c2d90370b7fe8acf886932..6ba51df47ed5c10b77182e8c10099e8386b6265e 100644
--- a/gcc/objc/objc-act.c
+++ b/gcc/objc/objc-act.c
@@ -441,7 +441,7 @@ objc_init ()
   /* Force the line number back to 0; check_newline will have
      raised it to 1, which will make the builtin functions appear
      not to be built in.  */
-  lineno = 0;
+  input_line = 0;
 
   /* If gen_declaration desired, open the output file.  */
   if (flag_gen_declaration)
@@ -1697,24 +1697,24 @@ build_module_descriptor ()
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_LONG]);
   field_decl = get_identifier ("version");
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   /* long  size; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_LONG]);
   field_decl = get_identifier ("size");
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* char  *name; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("name"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_symtab *symtab; */
@@ -1722,8 +1722,8 @@ build_module_descriptor ()
   decl_specs = get_identifier (UTAG_SYMTAB);
   decl_specs = build_tree_list (NULL_TREE, xref_tag (RECORD_TYPE, decl_specs));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("symtab"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   finish_struct (objc_module_template, field_decl_chain, NULL_TREE);
@@ -2049,12 +2049,12 @@ build_selector_translation_table ()
         if (!found)
           {
             /* Adjust line number for warning message.  */
-            int save_lineno = lineno;
+            int save_lineno = input_line;
             if (flag_next_runtime && TREE_PURPOSE (chain))
-              lineno = DECL_SOURCE_LINE (TREE_PURPOSE (chain));
+              input_line = DECL_SOURCE_LINE (TREE_PURPOSE (chain));
             warning ("creating selector for non existant method %s",
                      IDENTIFIER_POINTER (TREE_VALUE (chain)));
-            lineno = save_lineno;
+            input_line = save_lineno;
           }
       }
 
@@ -2565,8 +2565,8 @@ build_protocol_template ()
   decl_specs = build_tree_list (NULL_TREE, xref_tag (RECORD_TYPE,
 					get_identifier (UTAG_CLASS)));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("isa"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   /* char *protocol_name; */
@@ -2574,8 +2574,8 @@ build_protocol_template ()
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("protocol_name"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_protocol **protocol_list; */
@@ -2584,8 +2584,8 @@ build_protocol_template ()
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("protocol_list"));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, field_decl);
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_method_list *instance_methods; */
@@ -2596,8 +2596,8 @@ build_protocol_template ()
 				 get_identifier (UTAG_METHOD_PROTOTYPE_LIST)));
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("instance_methods"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_method_list *class_methods; */
@@ -2608,8 +2608,8 @@ build_protocol_template ()
 				 get_identifier (UTAG_METHOD_PROTOTYPE_LIST)));
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("class_methods"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   return finish_struct (template, field_decl_chain, NULL_TREE);
@@ -2672,9 +2672,8 @@ build_method_prototype_list_template (list_type, size)
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_INT]);
   field_decl = get_identifier ("method_count");
-
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   /* struct objc_method method_list[]; */
@@ -2682,9 +2681,8 @@ build_method_prototype_list_template (list_type, size)
   decl_specs = build_tree_list (NULL_TREE, list_type);
   field_decl = build_nt (ARRAY_REF, get_identifier ("method_list"),
 			 build_int_2 (size, 0));
-
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   finish_struct (objc_ivar_list_record, field_decl_chain, NULL_TREE);
@@ -2705,16 +2703,15 @@ build_method_prototype_template ()
   decl_specs = tree_cons (NULL_TREE, xref_tag (RECORD_TYPE,
 		          get_identifier (TAG_SELECTOR)), NULL_TREE);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("_cmd"));
-
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   decl_specs = tree_cons (NULL_TREE, ridpointers[(int) RID_CHAR], NULL_TREE);
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("method_types"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   finish_struct (proto_record, field_decl_chain, NULL_TREE);
@@ -3249,16 +3246,16 @@ build_category_template ()
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("category_name"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   /* char *class_name; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("class_name"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_method_list *instance_methods; */
@@ -3268,8 +3265,8 @@ build_category_template ()
 					  get_identifier (UTAG_METHOD_LIST)));
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("instance_methods"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_method_list *class_methods; */
@@ -3279,8 +3276,8 @@ build_category_template ()
 					  get_identifier (UTAG_METHOD_LIST)));
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("class_methods"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_protocol **protocol_list; */
@@ -3291,8 +3288,8 @@ build_category_template ()
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("protocol_list"));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, field_decl);
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   finish_struct (objc_category_template, field_decl_chain, NULL_TREE);
@@ -3316,16 +3313,16 @@ build_selector_template ()
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_VOID]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("sel_id"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   /* char *sel_type; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("sel_type"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   finish_struct (objc_selector_template, field_decl_chain, NULL_TREE);
@@ -3363,8 +3360,8 @@ build_class_template ()
 
   decl_specs = build_tree_list (NULL_TREE, objc_class_template);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("isa"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   /* struct objc_class *super_class; */
@@ -3372,40 +3369,40 @@ build_class_template ()
   decl_specs = build_tree_list (NULL_TREE, objc_class_template);
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("super_class"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* char *name; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("name"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* long version; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_LONG]);
   field_decl = get_identifier ("version");
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* long info; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_LONG]);
   field_decl = get_identifier ("info");
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* long instance_size; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_LONG]);
   field_decl = get_identifier ("instance_size");
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_ivar_list *ivars; */
@@ -3414,8 +3411,8 @@ build_class_template ()
 				xref_tag (RECORD_TYPE,
 					  get_identifier (UTAG_IVAR_LIST)));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("ivars"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* struct objc_method_list *methods; */
@@ -3424,8 +3421,8 @@ build_class_template ()
 				xref_tag (RECORD_TYPE,
 					  get_identifier (UTAG_METHOD_LIST)));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("methods"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   if (flag_next_runtime)
@@ -3436,7 +3433,7 @@ build_class_template ()
 				    xref_tag (RECORD_TYPE,
 					      get_identifier ("objc_cache")));
       field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("cache"));
-      field_decl = grokfield (input_filename, lineno, field_decl,
+      field_decl = grokfield (input_filename, input_line, field_decl,
 			      decl_specs, NULL_TREE);
       chainon (field_decl_chain, field_decl);
     }
@@ -3448,7 +3445,7 @@ build_class_template ()
 				    xref_tag (RECORD_TYPE,
 					      get_identifier ("sarray")));
       field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("dtable"));
-      field_decl = grokfield (input_filename, lineno, field_decl,
+      field_decl = grokfield (input_filename, input_line, field_decl,
 			      decl_specs, NULL_TREE);
       chainon (field_decl_chain, field_decl);
 
@@ -3457,7 +3454,7 @@ build_class_template ()
       decl_specs = build_tree_list (NULL_TREE, objc_class_template);
       field_decl
 	= build1 (INDIRECT_REF, NULL_TREE, get_identifier ("subclass_list"));
-      field_decl = grokfield (input_filename, lineno, field_decl,
+      field_decl = grokfield (input_filename, input_line, field_decl,
 			      decl_specs, NULL_TREE);
       chainon (field_decl_chain, field_decl);
 
@@ -3466,7 +3463,7 @@ build_class_template ()
       decl_specs = build_tree_list (NULL_TREE, objc_class_template);
       field_decl
 	= build1 (INDIRECT_REF, NULL_TREE, get_identifier ("sibling_class"));
-      field_decl = grokfield (input_filename, lineno, field_decl,
+      field_decl = grokfield (input_filename, input_line, field_decl,
 			      decl_specs, NULL_TREE);
       chainon (field_decl_chain, field_decl);
     }
@@ -3480,7 +3477,7 @@ build_class_template ()
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("protocol_list"));
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, field_decl);
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3488,16 +3485,16 @@ build_class_template ()
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_VOID]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("sel_id"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   /* void *gc_object_type; */
 
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_VOID]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("gc_object_type"));
-  field_decl
-    = grokfield (input_filename, lineno, field_decl, decl_specs, NULL_TREE);
+  field_decl = grokfield (input_filename, input_line,
+			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
   finish_struct (objc_class_template, field_decl_chain, NULL_TREE);
@@ -3624,7 +3621,7 @@ build_super_template ()
   decl_specs = build_tree_list (NULL_TREE, objc_object_reference);
   field_decl = get_identifier ("self");
   field_decl = build1 (INDIRECT_REF, NULL_TREE, field_decl);
-  field_decl = grokfield (input_filename, lineno,
+  field_decl = grokfield (input_filename, input_line,
 			  field_decl, decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
@@ -3634,7 +3631,7 @@ build_super_template ()
   decl_specs = build_tree_list (NULL_TREE, xref_tag (RECORD_TYPE, decl_specs));
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("class"));
 
-  field_decl = grokfield (input_filename, lineno,
+  field_decl = grokfield (input_filename, input_line,
 			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3668,7 +3665,7 @@ build_ivar_template ()
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("ivar_name"));
 
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
@@ -3677,7 +3674,7 @@ build_ivar_template ()
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_CHAR]);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("ivar_type"));
 
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3686,7 +3683,7 @@ build_ivar_template ()
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_INT]);
   field_decl = get_identifier ("ivar_offset");
 
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3715,7 +3712,7 @@ build_ivar_list_template (list_type, size)
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_INT]);
   field_decl = get_identifier ("ivar_count");
 
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
@@ -3725,7 +3722,7 @@ build_ivar_list_template (list_type, size)
   field_decl = build_nt (ARRAY_REF, get_identifier ("ivar_list"),
 			 build_int_2 (size, 0));
 
-  field_decl = grokfield (input_filename, lineno,
+  field_decl = grokfield (input_filename, input_line,
 			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3759,7 +3756,7 @@ build_method_list_template (list_type, size)
 		 get_identifier (UTAG_METHOD_PROTOTYPE_LIST)));
   field_decl
     = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("method_next"));
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
@@ -3768,7 +3765,7 @@ build_method_list_template (list_type, size)
   decl_specs = build_tree_list (NULL_TREE, ridpointers[(int) RID_INT]);
   field_decl = get_identifier ("method_count");
 
-  field_decl = grokfield (input_filename, lineno,
+  field_decl = grokfield (input_filename, input_line,
 			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3778,7 +3775,7 @@ build_method_list_template (list_type, size)
   field_decl = build_nt (ARRAY_REF, get_identifier ("method_list"),
 			 build_int_2 (size, 0));
 
-  field_decl = grokfield (input_filename, lineno,
+  field_decl = grokfield (input_filename, input_line,
 			  field_decl, decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3983,14 +3980,14 @@ build_method_template ()
 			  NULL_TREE);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("_cmd"));
 
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   field_decl_chain = field_decl;
 
   decl_specs = tree_cons (NULL_TREE, ridpointers[(int) RID_CHAR], NULL_TREE);
   field_decl = build1 (INDIRECT_REF, NULL_TREE,
 		       get_identifier ("method_types"));
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -3998,7 +3995,7 @@ build_method_template ()
 
   decl_specs = tree_cons (NULL_TREE, ridpointers[(int) RID_VOID], NULL_TREE);
   field_decl = build1 (INDIRECT_REF, NULL_TREE, get_identifier ("_imp"));
-  field_decl = grokfield (input_filename, lineno, field_decl,
+  field_decl = grokfield (input_filename, input_line, field_decl,
 			  decl_specs, NULL_TREE);
   chainon (field_decl_chain, field_decl);
 
@@ -5828,7 +5825,7 @@ add_instance_variable (class, public, declarator, declspecs, width)
   else
     CLASS_RAW_IVARS (class) = raw_decl;
 
-  field_decl = grokfield (input_filename, lineno,
+  field_decl = grokfield (input_filename, input_line,
 			  declarator, declspecs, width);
 
   /* Overload the public attribute, it is not used for FIELD_DECLs.  */
diff --git a/gcc/rtl-error.c b/gcc/rtl-error.c
index 00992b1977f807d5ff31a125eedac809e612a446..7526125f9a57425af49c65b597e3688980c79559 100644
--- a/gcc/rtl-error.c
+++ b/gcc/rtl-error.c
@@ -1,5 +1,5 @@
 /* RTL specific diagnostic subroutines for the GNU C compiler
-   Copyright (C) 2001, 2002 Free Software Foundation, Inc.
+   Copyright (C) 2001, 2002, 2003 Free Software Foundation, Inc.
    Contributed by Gabriel Dos Reis <gdr@codesourcery.com>
 
 This file is part of GCC.
@@ -69,7 +69,7 @@ file_and_line_for_asm (insn, pfile, pline)
   else
     {
       *pfile = input_filename;
-      *pline = lineno;
+      *pline = input_line;
     }
 }
 
diff --git a/gcc/scan.h b/gcc/scan.h
index 9f30bdecda25c5db35e3111697c6eb8985ee8ae8..d29f38a977a5a161a3e85a0ca705b2e915a07762 100644
--- a/gcc/scan.h
+++ b/gcc/scan.h
@@ -1,5 +1,5 @@
 /* scan.h - Utility declarations for scan-decls and fix-header programs.
-   Copyright (C) 1993, 1998, 1999 Free Software Foundation, Inc.
+   Copyright (C) 1993, 1998, 1999, 2003 Free Software Foundation, Inc.
 
 This program is free software; you can redistribute it and/or modify it
 under the terms of the GNU General Public License as published by the
@@ -52,7 +52,6 @@ struct fn_decl
 
 struct cpp_token;
 
-extern int lineno;
 extern void sstring_append _PARAMS((sstring *, sstring *));
 extern void make_sstring_space _PARAMS((sstring *, int));
 extern int skip_spaces _PARAMS((FILE *, int));
@@ -78,4 +77,4 @@ extern int get_token _PARAMS ((FILE *, sstring *));
 extern int source_lineno;
 extern sstring source_filename;
 /* Current physical line number */
-extern int lineno;
+extern int input_line;
diff --git a/gcc/toplev.c b/gcc/toplev.c
index e48eff36a072d958ae96a4a2fca2862a231d0945..0aee80f308aa98e2f0ccc607d64d773599952f47 100644
--- a/gcc/toplev.c
+++ b/gcc/toplev.c
@@ -162,7 +162,7 @@ const char *main_input_filename;
 
 /* Current line number in real source file.  */
 
-int lineno;
+int input_line;
 
 /* Nonzero if it is unsafe to create any new pseudo registers.  */
 int no_new_pseudos;
@@ -2149,12 +2149,12 @@ push_srcloc (file, line)
   if (input_file_stack)
     {
       input_file_stack->name = input_filename;
-      input_file_stack->line = lineno;
+      input_file_stack->line = input_line;
     }
 
   fs = (struct file_stack *) xmalloc (sizeof (struct file_stack));
   fs->name = input_filename = file;
-  fs->line = lineno = line;
+  fs->line = input_line = line;
   fs->next = input_file_stack;
   input_file_stack = fs;
   input_file_stack_tick++;
@@ -2177,12 +2177,12 @@ pop_srcloc ()
   if (input_file_stack)
     {
       input_filename = input_file_stack->name;
-      lineno = input_file_stack->line;
+      input_line = input_file_stack->line;
     }
   else
     {
       input_filename = NULL;
-      lineno = 0;
+      input_line = 0;
     }
 }
 
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index 3a8adc51e2ee8a0aa0a33603ceb1f0280ed6f17e..cb6b0c49b8e51ce314819d37b1404270160af1aa 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -1,5 +1,5 @@
 /* Control and data flow functions for trees.
-   Copyright 2001, 2002 Free Software Foundation, Inc.
+   Copyright 2001, 2002, 2003 Free Software Foundation, Inc.
    Contributed by Alexandre Oliva <aoliva@redhat.com>
 
 This file is part of GCC.
@@ -900,10 +900,10 @@ static tree
 find_alloca_call (exp)
      tree exp;
 {
-  int line = lineno;
+  int line = input_line;
   const char *file = input_filename;
   tree ret = walk_tree (&exp, find_alloca_call_1, NULL, NULL);
-  lineno = line;
+  input_line = line;
   input_filename = file;
   return ret;
 }
@@ -931,10 +931,10 @@ static tree
 find_builtin_longjmp_call (exp)
      tree exp;
 {
-  int line = lineno;
+  int line = input_line;
   const char *file = input_filename;
   tree ret = walk_tree (&exp, find_builtin_longjmp_call_1, NULL, NULL);
-  lineno = line;
+  input_line = line;
   input_filename = file;
   return ret;
 }
@@ -1639,7 +1639,7 @@ walk_tree (tp, func, data, htab_)
       /* Set lineno here so we get the right instantiation context
 	 if we call instantiate_decl from inlinable_function_p.  */
       if (STATEMENT_CODE_P (code) && !STMT_LINENO_FOR_FN_P (*tp))
-	lineno = STMT_LINENO (*tp);
+	input_line = STMT_LINENO (*tp);
 #endif /* not INLINER_FOR_JAVA */
 
       /* Walk over all the sub-trees of this operand.  */
diff --git a/gcc/tree.c b/gcc/tree.c
index 7deaa65640982f558a6c6d0fc80e9c3e595f4c14..8cff4ce0e2fc14e6eecdd28b23ecf02cade785e0 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -1,6 +1,6 @@
 /* Language-independent node constructors for parse phase of GNU compiler.
    Copyright (C) 1987, 1988, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
-   1999, 2000, 2001, 2002 Free Software Foundation, Inc.
+   1999, 2000, 2001, 2002, 2003 Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -308,7 +308,7 @@ make_node (code)
 	DECL_ALIGN (t) = 1;
       DECL_USER_ALIGN (t) = 0;
       DECL_IN_SYSTEM_HEADER (t) = in_system_header;
-      DECL_SOURCE_LINE (t) = lineno;
+      DECL_SOURCE_LINE (t) = input_line;
       DECL_SOURCE_FILE (t) =
 	(input_filename) ? input_filename : "<built-in>";
       DECL_UID (t) = next_decl_uid++;
diff --git a/gcc/tree.h b/gcc/tree.h
index fd6420aacffeaf3ece84ca82ff8424d41ca32a95..791be350da7cb4f6ea340ecbd332a2dea52576cc 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -2783,7 +2783,7 @@ extern int real_zerop PARAMS ((tree));
 extern const char *input_filename;
 
 /* Current line number in input file.  */
-extern int lineno;
+extern int input_line;
 
 /* Nonzero means lvalues are limited to those valid in pedantic ANSI C.
    Zero means allow extended lvalues.  */
diff --git a/gcc/treelang/ChangeLog b/gcc/treelang/ChangeLog
index 58e473320e87d3691b37ded46ac3ffc74bf1f327..0c30bdba7e64a90555b36cee717f951e02307f99 100644
--- a/gcc/treelang/ChangeLog
+++ b/gcc/treelang/ChangeLog
@@ -1,3 +1,7 @@
+2003-05-01  Nathan Sidwell  <nathan@codesourcery.com>
+
+	* tree1.c (treelang_init): Rename lineno to input_line.
+
 2003-04-30  Steven Bosscher  <steven@gcc.gnu.org>
 
 	* parse.y (make_plus_expression): New function.
diff --git a/gcc/treelang/tree1.c b/gcc/treelang/tree1.c
index 6333d0fc0abbcbcf90f434e01e76a0f5873d9c9d..ad5622a7ddd39f9837c4a585983c9e177c707ec6 100644
--- a/gcc/treelang/tree1.c
+++ b/gcc/treelang/tree1.c
@@ -190,7 +190,7 @@ treelang_init ()
   in_fname = main_input_filename;
 
   /* Set up the declarations needed for this front end.  */
-  lineno = 0;
+  input_line = 0;
 
   /* Init decls etc.  */