diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index a58362ac50440a3473168f3a06519555aad972c8..f7f058d55c3f789ec2d6f9a167d1489481c77c10 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,23 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* diagnostic.c (fatal_error (const char *, ...)): Remove function.
+	* diagnostic-core.h (fatal_error (const char *, ...)): Remove
+	prototype.
+	* toplev.h (init_asm_output): Update comment on use of
+	UNKNOWN_LOCATION with fatal_error.
+	* cgraph.c, collect-utils.c, collect2.c, config/arc/arc.c,
+	config/arc/arc.md, config/avr/avr.c, config/c6x/c6x.h,
+	config/darwin.c, config/host-darwin.c, config/i386/host-cygwin.c,
+	config/i386/intelmic-mkoffload.c, config/nios2/nios2.c,
+	config/nvptx/mkoffload.c, config/nvptx/nvptx.h,
+	config/rs6000/host-darwin.c, config/rs6000/rs6000.c,
+	config/s390/s390.c, gcc.c, gcov-io.h, gcov-tool.c, ggc-common.c,
+	ggc-page.c, graph.c, ipa-inline-analysis.c, ipa-reference.c,
+	lto-cgraph.c, lto-section-in.c, lto-streamer-in.c, lto-streamer.c,
+	lto-wrapper.c, objc/objc-act.c, opts.c, passes.c, plugin.c,
+	tlink.c, toplev.c, tree-streamer-in.c, varpool.c: All callers of
+	fatal_error changed to pass input_location as first argument.
+
 2015-01-30  Martin Liska  <mliska@suse.cz>
 
 	* tree.h: Change GCC_VERSION >= 4004 to GCC_VERSION >= 4006
diff --git a/gcc/c-family/ChangeLog b/gcc/c-family/ChangeLog
index 851e664503fc5432a182059c1e97016cd57b8a91..9764b7c144aee2762cc4fe283e332dc4fa57642f 100644
--- a/gcc/c-family/ChangeLog
+++ b/gcc/c-family/ChangeLog
@@ -1,3 +1,8 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* c-opts.c, c-pch.c, cppspec.c: All callers of fatal_error changed
+	to pass input_location as first argument.
+
 2015-01-23  Tom de Vries  <tom@codesourcery.com>
 
 	PR libgomp/64672
diff --git a/gcc/c-family/c-opts.c b/gcc/c-family/c-opts.c
index 124c91c700f196a183d4a9eb90a8a49f5842ace1..d10e5bd8daaeeeac3ad52e6b2bb6bdadaeebd91e 100644
--- a/gcc/c-family/c-opts.c
+++ b/gcc/c-family/c-opts.c
@@ -928,7 +928,7 @@ c_common_post_options (const char **pfilename)
 
       if (out_stream == NULL)
 	{
-	  fatal_error ("opening output file %s: %m", out_fname);
+	  fatal_error (input_location, "opening output file %s: %m", out_fname);
 	  return false;
 	}
 
@@ -1111,7 +1111,8 @@ c_common_finish (void)
 	{
 	  deps_stream = fopen (deps_file, deps_append ? "a": "w");
 	  if (!deps_stream)
-	    fatal_error ("opening dependency file %s: %m", deps_file);
+	    fatal_error (input_location, "opening dependency file %s: %m",
+			 deps_file);
 	}
     }
 
@@ -1121,10 +1122,10 @@ c_common_finish (void)
 
   if (deps_stream && deps_stream != out_stream
       && (ferror (deps_stream) || fclose (deps_stream)))
-    fatal_error ("closing dependency file %s: %m", deps_file);
+    fatal_error (input_location, "closing dependency file %s: %m", deps_file);
 
   if (out_stream && (ferror (out_stream) || fclose (out_stream)))
-    fatal_error ("when writing output to %s: %m", out_fname);
+    fatal_error (input_location, "when writing output to %s: %m", out_fname);
 }
 
 /* Either of two environment variables can specify output of
diff --git a/gcc/c-family/c-pch.c b/gcc/c-family/c-pch.c
index 599b600dc66d69c1320506824c59a0db9e62e4fd..0ede92ab7ccf9856f4e45cff8053d30e17e65948 100644
--- a/gcc/c-family/c-pch.c
+++ b/gcc/c-family/c-pch.c
@@ -122,7 +122,8 @@ pch_init (void)
 
   f = fopen (pch_file, "w+b");
   if (f == NULL)
-    fatal_error ("can%'t create precompiled header %s: %m", pch_file);
+    fatal_error (input_location, "can%'t create precompiled header %s: %m",
+		 pch_file);
   pch_outfile = f;
 
   gcc_assert (memcmp (executable_checksum, no_checksum, 16) != 0);
@@ -144,7 +145,7 @@ pch_init (void)
       || fwrite (executable_checksum, 16, 1, f) != 1
       || fwrite (&v, sizeof (v), 1, f) != 1
       || fwrite (target_validity, v.target_data_length, 1, f) != 1)
-    fatal_error ("can%'t write to %s: %m", pch_file);
+    fatal_error (input_location, "can%'t write to %s: %m", pch_file);
 
   /* Let the debugging format deal with the PCHness.  */
   (*debug_hooks->handle_pch) (0);
@@ -202,7 +203,7 @@ c_common_write_pch (void)
 
   if (fseek (pch_outfile, 0, SEEK_SET) != 0
       || fwrite (get_ident (), IDENT_LENGTH, 1, pch_outfile) != 1)
-    fatal_error ("can%'t write %s: %m", pch_file);
+    fatal_error (input_location, "can%'t write %s: %m", pch_file);
 
   fclose (pch_outfile);
 
@@ -230,7 +231,7 @@ c_common_valid_pch (cpp_reader *pfile, const char *name, int fd)
 
   sizeread = read (fd, ident, IDENT_LENGTH + 16);
   if (sizeread == -1)
-    fatal_error ("can%'t read %s: %m", name);
+    fatal_error (input_location, "can%'t read %s: %m", name);
   else if (sizeread != IDENT_LENGTH + 16)
     {
       if (cpp_get_options (pfile)->warn_invalid_pch)
@@ -271,7 +272,7 @@ c_common_valid_pch (cpp_reader *pfile, const char *name, int fd)
      executable, so it ought to be long enough that we can read a
      c_pch_validity structure.  */
   if (read (fd, &v, sizeof (v)) != sizeof (v))
-    fatal_error ("can%'t read %s: %m", name);
+    fatal_error (input_location, "can%'t read %s: %m", name);
 
   /* The allowable debug info combinations are that either the PCH file
      was built with the same as is being used now, or the PCH file was
@@ -322,7 +323,7 @@ c_common_valid_pch (cpp_reader *pfile, const char *name, int fd)
 
     if ((size_t) read (fd, this_file_data, v.target_data_length)
 	!= v.target_data_length)
-      fatal_error ("can%'t read %s: %m", name);
+      fatal_error (input_location, "can%'t read %s: %m", name);
     msg = targetm.pch_valid_p (this_file_data, v.target_data_length);
     free (this_file_data);
     if (msg != NULL)
@@ -435,13 +436,13 @@ c_common_pch_pragma (cpp_reader *pfile, const char *name)
 
   fd = open (name, O_RDONLY | O_BINARY, 0666);
   if (fd == -1)
-    fatal_error ("%s: couldn%'t open PCH file: %m", name);
+    fatal_error (input_location, "%s: couldn%'t open PCH file: %m", name);
 
   if (c_common_valid_pch (pfile, name, fd) != 1)
     {
       if (!cpp_get_options (pfile)->warn_invalid_pch)
 	inform (input_location, "use -Winvalid-pch for more information");
-      fatal_error ("%s: PCH file was invalid", name);
+      fatal_error (input_location, "%s: PCH file was invalid", name);
     }
 
   c_common_read_pch (pfile, name, fd, name);
diff --git a/gcc/c-family/cppspec.c b/gcc/c-family/cppspec.c
index a49371ad199584ad6701c51a2378046aa0ab1724..55e368b24e6568b33edfb9b310253857e816629b 100644
--- a/gcc/c-family/cppspec.c
+++ b/gcc/c-family/cppspec.c
@@ -89,7 +89,8 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
 
 	case OPT_S:
 	case OPT_c:
-	  fatal_error ("%qs is not a valid option to the preprocessor",
+	  fatal_error (input_location,
+		       "%qs is not a valid option to the preprocessor",
 		       decoded_options[i].orig_option_with_args_text);
 	  return;
 
@@ -108,7 +109,7 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
 		seen_input++;
 		if (seen_input == 3)
 		  {
-		    fatal_error ("too many input files");
+		    fatal_error (input_location, "too many input files");
 		    return;
 		  }
 		else if (seen_input == 2)
diff --git a/gcc/cgraph.c b/gcc/cgraph.c
index 29090a209e5a74c58f59d18d04722220b781e738..89d0d2feb9fdfa823f13b5a1a7fbae23c87499cd 100644
--- a/gcc/cgraph.c
+++ b/gcc/cgraph.c
@@ -3188,7 +3188,7 @@ cgraph_node::get_untransformed_body (void)
   data = lto_get_section_data (file_data, LTO_section_function_body,
 			       name, &len);
   if (!data)
-    fatal_error ("%s: section %s is missing",
+    fatal_error (input_location, "%s: section %s is missing",
 		 file_data->file_name,
 		 name);
 
diff --git a/gcc/collect-utils.c b/gcc/collect-utils.c
index 001fb2825ee62eb928aef1432b5eb4e2c94da4b6..6bbe9eb86980e3f033e4b29f48e457e5c27e1439 100644
--- a/gcc/collect-utils.c
+++ b/gcc/collect-utils.c
@@ -65,7 +65,7 @@ collect_wait (const char *prog, struct pex_obj *pex)
   int status;
 
   if (!pex_get_status (pex, 1, &status))
-    fatal_error ("can't get program status: %m");
+    fatal_error (input_location, "can't get program status: %m");
   pex_free (pex);
 
   if (status)
@@ -73,7 +73,7 @@ collect_wait (const char *prog, struct pex_obj *pex)
       if (WIFSIGNALED (status))
 	{
 	  int sig = WTERMSIG (status);
-	  fatal_error ("%s terminated with signal %d [%s]%s",
+	  fatal_error (input_location, "%s terminated with signal %d [%s]%s",
 		       prog, sig, strsignal (sig),
 		       WCOREDUMP (status) ? ", core dumped" : "");
 	}
@@ -89,7 +89,7 @@ do_wait (const char *prog, struct pex_obj *pex)
 {
   int ret = collect_wait (prog, pex);
   if (ret != 0)
-    fatal_error ("%s returned %d exit status", prog, ret);
+    fatal_error (input_location, "%s returned %d exit status", prog, ret);
 
   if (response_file && !save_temps)
     {
@@ -130,17 +130,20 @@ collect_execute (const char *prog, char **argv, const char *outname,
       f = fopen (response_file, "w");
 
       if (f == NULL)
-        fatal_error ("could not open response file %s", response_file);
+        fatal_error (input_location, "could not open response file %s",
+		     response_file);
 
       status = writeargv (current_argv, f);
 
       if (status)
-        fatal_error ("could not write to response file %s", response_file);
+        fatal_error (input_location, "could not write to response file %s",
+		     response_file);
 
       status = fclose (f);
 
       if (EOF == status)
-        fatal_error ("could not close response file %s", response_file);
+        fatal_error (input_location, "could not close response file %s",
+		     response_file);
 
       response_arg = concat ("@", response_file, NULL);
       response_argv[0] = argv0;
@@ -173,11 +176,11 @@ collect_execute (const char *prog, char **argv, const char *outname,
      since we might not end up needing something that we could not find.  */
 
   if (argv[0] == 0)
-    fatal_error ("cannot find '%s'", prog);
+    fatal_error (input_location, "cannot find '%s'", prog);
 
   pex = pex_init (0, "collect2", NULL);
   if (pex == NULL)
-    fatal_error ("pex_init failed: %m");
+    fatal_error (input_location, "pex_init failed: %m");
 
   errmsg = pex_run (pex, flags, argv[0], argv, outname,
 		    errname, &err);
@@ -186,10 +189,10 @@ collect_execute (const char *prog, char **argv, const char *outname,
       if (err != 0)
 	{
 	  errno = err;
-	  fatal_error ("%s: %m", _(errmsg));
+	  fatal_error (input_location, "%s: %m", _(errmsg));
 	}
       else
-	fatal_error (errmsg);
+	fatal_error (input_location, errmsg);
     }
 
   free (response_arg);
diff --git a/gcc/collect2.c b/gcc/collect2.c
index 2bfe00891ddf009bcad55623e3f97f16dde10c6a..b53e15189df6d2550f266b539a2d0c26a05dd771 100644
--- a/gcc/collect2.c
+++ b/gcc/collect2.c
@@ -699,7 +699,7 @@ maybe_run_lto_and_relink (char **lto_ld_argv, char **object_lst,
       size_t num_files;
 
       if (!lto_wrapper)
-	fatal_error ("COLLECT_LTO_WRAPPER must be set");
+	fatal_error (input_location, "COLLECT_LTO_WRAPPER must be set");
 
       num_lto_c_args++;
 
@@ -963,7 +963,7 @@ main (int argc, char **argv)
   diagnostic_initialize (global_dc, 0);
 
   if (atexit (collect_atexit) != 0)
-    fatal_error ("atexit failed");
+    fatal_error (input_location, "atexit failed");
 
   /* Do not invoke xcalloc before this point, since locale needs to be
      set first, in case a diagnostic is issued.  */
@@ -1061,7 +1061,7 @@ main (int argc, char **argv)
   c_ptr = CONST_CAST2 (const char **, char **, c_argv);
 
   if (argc < 2)
-    fatal_error ("no arguments");
+    fatal_error (input_location, "no arguments");
 
 #ifdef SIGQUIT
   if (signal (SIGQUIT, SIG_IGN) != SIG_IGN)
@@ -1341,7 +1341,8 @@ main (int argc, char **argv)
 
 		  stream = fopen (list_filename, "r");
 		  if (stream == NULL)
-		    fatal_error ("can't open %s: %m", list_filename);
+		    fatal_error (input_location, "can't open %s: %m",
+				 list_filename);
 
 		  while (fgets (buf, sizeof buf, stream) != NULL)
 		    {
@@ -1542,10 +1543,10 @@ main (int argc, char **argv)
 
       exportf = fopen (export_file, "w");
       if (exportf == (FILE *) 0)
-	fatal_error ("fopen %s: %m", export_file);
+	fatal_error (input_location, "fopen %s: %m", export_file);
       write_aix_file (exportf, exports.first);
       if (fclose (exportf))
-	fatal_error ("fclose %s: %m", export_file);
+	fatal_error (input_location, "fclose %s: %m", export_file);
     }
 #endif
 
@@ -1725,12 +1726,12 @@ main (int argc, char **argv)
   maybe_unlink (output_file);
   outf = fopen (c_file, "w");
   if (outf == (FILE *) 0)
-    fatal_error ("fopen %s: %m", c_file);
+    fatal_error (input_location, "fopen %s: %m", c_file);
 
   write_c_file (outf, c_file);
 
   if (fclose (outf))
-    fatal_error ("fclose %s: %m", c_file);
+    fatal_error (input_location, "fclose %s: %m", c_file);
 
   /* Tell the linker that we have initializer and finalizer functions.  */
 #ifdef LD_INIT_SWITCH
@@ -1765,10 +1766,10 @@ main (int argc, char **argv)
 #endif
       exportf = fopen (export_file, "w");
       if (exportf == (FILE *) 0)
-	fatal_error ("fopen %s: %m", export_file);
+	fatal_error (input_location, "fopen %s: %m", export_file);
       write_aix_file (exportf, exports.first);
       if (fclose (exportf))
-	fatal_error ("fclose %s: %m", export_file);
+	fatal_error (input_location, "fclose %s: %m", export_file);
     }
 #endif
 
@@ -2320,7 +2321,7 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
 
   /* If we do not have an `nm', complain.  */
   if (nm_file_name == 0)
-    fatal_error ("cannot find 'nm'");
+    fatal_error (input_location, "cannot find 'nm'");
 
   nm_argv[argc++] = nm_file_name;
   if (NM_FLAGS[0] != '\0')
@@ -2346,7 +2347,7 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
 
   pex = pex_init (PEX_USE_PIPES, "collect2", NULL);
   if (pex == NULL)
-    fatal_error ("pex_init failed: %m");
+    fatal_error (input_location, "pex_init failed: %m");
 
   errmsg = pex_run (pex, 0, nm_file_name, real_nm_argv, NULL, HOST_BIT_BUCKET,
 		    &err);
@@ -2355,10 +2356,10 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
       if (err != 0)
 	{
 	  errno = err;
-	  fatal_error ("%s: %m", _(errmsg));
+	  fatal_error (input_location, "%s: %m", _(errmsg));
 	}
       else
-	fatal_error (errmsg);
+	fatal_error (input_location, errmsg);
     }
 
   int_handler  = (void (*) (int)) signal (SIGINT,  SIG_IGN);
@@ -2368,7 +2369,7 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
 
   inf = pex_read_output (pex, 0);
   if (inf == NULL)
-    fatal_error ("can't open nm output: %m");
+    fatal_error (input_location, "can't open nm output: %m");
 
   if (debug)
     {
@@ -2452,7 +2453,8 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
 	  if (! (filter & SCAN_INIT))
 	    break;
 	  if (which_pass != PASS_LIB)
-	    fatal_error ("init function found in object %s", prog_name);
+	    fatal_error (input_location, "init function found in object %s",
+			 prog_name);
 #ifndef LD_INIT_SWITCH
 	  add_to_list (&constructors, name);
 #endif
@@ -2462,7 +2464,8 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
 	  if (! (filter & SCAN_FINI))
 	    break;
 	  if (which_pass != PASS_LIB)
-	    fatal_error ("fini function found in object %s", prog_name);
+	    fatal_error (input_location, "fini function found in object %s",
+			 prog_name);
 #ifndef LD_FINI_SWITCH
 	  add_to_list (&destructors, name);
 #endif
@@ -2543,7 +2546,7 @@ scan_libraries (const char *prog_name)
 
   pex = pex_init (PEX_USE_PIPES, "collect2", NULL);
   if (pex == NULL)
-    fatal_error ("pex_init failed: %m");
+    fatal_error (input_location, "pex_init failed: %m");
 
   errmsg = pex_run (pex, 0, ldd_file_name, real_ldd_argv, NULL, NULL, &err);
   if (errmsg != NULL)
@@ -2551,10 +2554,10 @@ scan_libraries (const char *prog_name)
       if (err != 0)
 	{
 	  errno = err;
-	  fatal_error ("%s: %m", _(errmsg));
+	  fatal_error (input_location, "%s: %m", _(errmsg));
 	}
       else
-	fatal_error (errmsg);
+	fatal_error (input_location, errmsg);
     }
 
   int_handler  = (void (*) (int)) signal (SIGINT,  SIG_IGN);
@@ -2564,7 +2567,7 @@ scan_libraries (const char *prog_name)
 
   inf = pex_read_output (pex, 0);
   if (inf == NULL)
-    fatal_error ("can't open ldd output: %m");
+    fatal_error (input_location, "can't open ldd output: %m");
 
   if (debug)
     notice ("\nldd output with constructors/destructors.\n");
@@ -2582,7 +2585,7 @@ scan_libraries (const char *prog_name)
 
       name = p;
       if (strncmp (name, "not found", sizeof ("not found") - 1) == 0)
-	fatal_error ("dynamic dependency %s not found", buf);
+	fatal_error (input_location, "dynamic dependency %s not found", buf);
 
       /* Find the end of the symbol name.  */
       for (end = p;
@@ -2594,7 +2597,8 @@ scan_libraries (const char *prog_name)
       if (access (name, R_OK) == 0)
 	add_to_list (&libraries, name);
       else
-	fatal_error ("unable to open dynamic dependency '%s'", buf);
+	fatal_error (input_location, "unable to open dynamic dependency '%s'",
+		     buf);
 
       if (debug)
 	fprintf (stderr, "\t%s\n", buf);
@@ -2757,7 +2761,7 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
       if ((ldptr = ldopen (CONST_CAST (char *, prog_name), ldptr)) != NULL)
 	{
 	  if (! MY_ISCOFF (HEADER (ldptr).f_magic))
-	    fatal_error ("%s: not a COFF file", prog_name);
+	    fatal_error (input_location, "%s: not a COFF file", prog_name);
 
 	  if (GCC_CHECK_HDR (ldptr))
 	    {
@@ -2906,7 +2910,8 @@ scan_prog_file (const char *prog_name, scanpass which_pass,
 	}
       else
 	{
-	  fatal_error ("%s: cannot open as COFF file", prog_name);
+	  fatal_error (input_location, "%s: cannot open as COFF file",
+		       prog_name);
 	}
 #ifdef COLLECT_EXPORT_LIST
       /* On AIX loop continues while there are more members in archive.  */
@@ -2964,7 +2969,7 @@ resolve_lib_name (const char *name)
   if (debug)
     fprintf (stderr, "not found\n");
   else
-    fatal_error ("library lib%s not found", name);
+    fatal_error (input_location, "library lib%s not found", name);
   return (NULL);
 }
 #endif /* COLLECT_EXPORT_LIST */
diff --git a/gcc/config/arc/arc.c b/gcc/config/arc/arc.c
index ab00ed2a70db457a3679912b585bfd2a2c1d7650..74089e8f413c2bfb51d877b133da673ec1344923 100644
--- a/gcc/config/arc/arc.c
+++ b/gcc/config/arc/arc.c
@@ -5492,7 +5492,8 @@ check_if_valid_sleep_operand (rtx *operands, int opno)
 	if( UNSIGNED_INT6 (INTVAL (operands[opno])))
 	    return true;
     default:
-	fatal_error("operand for sleep instruction must be an unsigned 6 bit compile-time constant");
+	fatal_error (input_location,
+		     "operand for sleep instruction must be an unsigned 6 bit compile-time constant");
 	break;
     }
   return false;
@@ -6044,7 +6045,7 @@ arc_reorg (void)
       cfun->machine->ccfsm_current_insn = NULL_RTX;
 
       if (!INSN_ADDRESSES_SET_P())
-	  fatal_error ("Insn addresses not set after shorten_branches");
+	  fatal_error (input_location, "Insn addresses not set after shorten_branches");
 
       for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
 	{
@@ -6248,7 +6249,7 @@ arc_reorg (void)
     } while (changed);
 
   if (INSN_ADDRESSES_SET_P())
-    fatal_error ("insn addresses not freed");
+    fatal_error (input_location, "insn addresses not freed");
 
   arc_reorg_in_progress = 0;
 }
diff --git a/gcc/config/arc/arc.md b/gcc/config/arc/arc.md
index 8fabf5e6fbbcf27caacbb1f764205727c5a830b2..d66441f326b150dbdd3c028e1a72f9a413ac30f3 100644
--- a/gcc/config/arc/arc.md
+++ b/gcc/config/arc/arc.md
@@ -4292,7 +4292,8 @@
 
   /* Keep this message in sync with the one in arc.c:arc_expand_builtin,
      because *.md files do not get scanned by exgettext.  */
-  fatal_error (\"operand to trap_s should be an unsigned 6-bit value\");
+  fatal_error (input_location,
+	       \"operand to trap_s should be an unsigned 6-bit value\");
 }
   [(set_attr "length" "2")
   (set_attr "type" "misc")])
diff --git a/gcc/config/avr/avr.c b/gcc/config/avr/avr.c
index c7074f079043606bbaad1c9c15319252f6da744b..f69ba38616b6485e929ba5bec7d65b5c0a860460 100644
--- a/gcc/config/avr/avr.c
+++ b/gcc/config/avr/avr.c
@@ -381,7 +381,7 @@ avr_option_override (void)
   for (avr_current_device = avr_mcu_types; ; avr_current_device++)
     {
       if (!avr_current_device->name)
-        fatal_error ("mcu not found");
+        fatal_error (input_location, "mcu not found");
       if (!avr_current_device->macro
           && avr_current_device->arch == avr_arch_index)
         break;
diff --git a/gcc/config/c6x/c6x.h b/gcc/config/c6x/c6x.h
index fd7c83377c984f7db56833548869f5091c65acce..58a7ac63a8983e687dd0c1773c4811f7b151e64b 100644
--- a/gcc/config/c6x/c6x.h
+++ b/gcc/config/c6x/c6x.h
@@ -359,7 +359,8 @@ struct c6x_args {
 #define DEFAULT_PCC_STRUCT_RETURN 0
 
 #define FUNCTION_PROFILER(file, labelno) \
-  fatal_error ("profiling is not yet implemented for this architecture")
+  fatal_error (input_location, \
+	       "profiling is not yet implemented for this architecture")
 
 
 /* Trampolines.  */
diff --git a/gcc/config/darwin.c b/gcc/config/darwin.c
index 896f2ad23dadec8f89e2344ad1cbb025fd7552c9..40804b8d11af6bd124ed884e595bed3781795515 100644
--- a/gcc/config/darwin.c
+++ b/gcc/config/darwin.c
@@ -1949,7 +1949,8 @@ darwin_asm_lto_start (void)
     lto_asm_out_name = make_temp_file (".lto.s");
   lto_asm_out_file = fopen (lto_asm_out_name, "a");
   if (lto_asm_out_file == NULL)
-    fatal_error ("failed to open temporary file %s for LTO output",
+    fatal_error (input_location,
+		 "failed to open temporary file %s for LTO output",
 		 lto_asm_out_name);
   asm_out_file = lto_asm_out_file;
 }
@@ -2942,7 +2943,8 @@ darwin_file_end (void)
 
       lto_asm_out_file = fopen (lto_asm_out_name, "r");
       if (lto_asm_out_file == NULL)
-	fatal_error ("failed to open temporary file %s with LTO output",
+	fatal_error (input_location,
+		     "failed to open temporary file %s with LTO output",
 		     lto_asm_out_name);
       fseek (lto_asm_out_file, 0, SEEK_END);
       n = ftell (lto_asm_out_file);
diff --git a/gcc/config/host-darwin.c b/gcc/config/host-darwin.c
index 5582c230e5bc5f01905bd49c6333ad4ad1ac87eb..0919867526f85c84660ebb1f7927a063cf9befe8 100644
--- a/gcc/config/host-darwin.c
+++ b/gcc/config/host-darwin.c
@@ -58,7 +58,7 @@ darwin_gt_pch_use_address (void *addr, size_t sz, int fd, size_t off)
   sz = (sz + pagesize - 1) / pagesize * pagesize;
 
   if (munmap (pch_address_space + sz, sizeof (pch_address_space) - sz) != 0)
-    fatal_error ("couldn%'t unmap pch_address_space: %m");
+    fatal_error (input_location, "couldn%'t unmap pch_address_space: %m");
 
   if (ret)
     {
diff --git a/gcc/config/i386/host-cygwin.c b/gcc/config/i386/host-cygwin.c
index 7575b8ed2e031b844d2387568e627932d18103ce..71ce41bb5a3c934fda63d63c900565f4b647aefb 100644
--- a/gcc/config/i386/host-cygwin.c
+++ b/gcc/config/i386/host-cygwin.c
@@ -52,14 +52,14 @@ cygwin_gt_pch_get_address (size_t sz, int fd)
   off_t p = lseek(fd, 0, SEEK_CUR);
 
   if (p == (off_t) -1)
-    fatal_error ("can%'t get position in PCH file: %m");
+    fatal_error (input_location, "can%'t get position in PCH file: %m");
 
    /* Cygwin requires that the underlying file be at least
       as large as the requested mapping.  */
   if ((size_t) p < sz)
   { 
     if ( ftruncate (fd, sz) == -1 )
-      fatal_error ("can%'t extend PCH file: %m");
+      fatal_error (input_location, "can%'t extend PCH file: %m");
   }
 
   base = mmap (NULL, sz, PROT_READ | PROT_WRITE, MAP_PRIVATE, fd, 0);
@@ -70,7 +70,7 @@ cygwin_gt_pch_get_address (size_t sz, int fd)
     munmap (base, sz);
 
   if (lseek (fd, p, SEEK_SET) == (off_t) -1 )
-    fatal_error ("can%'t set position in PCH file: %m");
+    fatal_error (input_location, "can%'t set position in PCH file: %m");
 
   return base;
 }
diff --git a/gcc/config/i386/intelmic-mkoffload.c b/gcc/config/i386/intelmic-mkoffload.c
index edc3f92ea010b5480f6aad6dc3a146bd98e7e9af..e6394e9a549e2144df6f0a545116843ee0bb6a4b 100644
--- a/gcc/config/i386/intelmic-mkoffload.c
+++ b/gcc/config/i386/intelmic-mkoffload.c
@@ -227,7 +227,7 @@ generate_target_descr_file (const char *target_compiler)
   FILE *src_file = fopen (src_filename, "w");
 
   if (!src_file)
-    fatal_error ("cannot open '%s'", src_filename);
+    fatal_error (input_location, "cannot open '%s'", src_filename);
 
   fprintf (src_file,
 	   "extern void *__offload_funcs_end[];\n"
@@ -287,7 +287,7 @@ generate_target_offloadend_file (const char *target_compiler)
   FILE *src_file = fopen (src_filename, "w");
 
   if (!src_file)
-    fatal_error ("cannot open '%s'", src_filename);
+    fatal_error (input_location, "cannot open '%s'", src_filename);
 
   fprintf (src_file,
 	   "void *__offload_funcs_end[0]\n"
@@ -324,7 +324,7 @@ generate_host_descr_file (const char *host_compiler)
   FILE *src_file = fopen (src_filename, "w");
 
   if (!src_file)
-    fatal_error ("cannot open '%s'", src_filename);
+    fatal_error (input_location, "cannot open '%s'", src_filename);
 
   fprintf (src_file,
 	   "extern void *__OFFLOAD_TABLE__;\n"
@@ -401,7 +401,7 @@ prepare_target_image (const char *target_compiler, int argc, char **argv)
 	obstack_ptr_grow (&argv_obstack, argv[i]);
     }
   if (!out_obj_filename)
-    fatal_error ("output file not specified");
+    fatal_error (input_location, "output file not specified");
   obstack_ptr_grow (&argv_obstack, opt2);
   obstack_ptr_grow (&argv_obstack, "-o");
   obstack_ptr_grow (&argv_obstack, target_so_filename);
@@ -477,17 +477,18 @@ main (int argc, char **argv)
   diagnostic_initialize (global_dc, 0);
 
   if (atexit (mkoffload_atexit) != 0)
-    fatal_error ("atexit failed");
+    fatal_error (input_location, "atexit failed");
 
   const char *host_compiler = getenv ("COLLECT_GCC");
   if (!host_compiler)
-    fatal_error ("COLLECT_GCC must be set");
+    fatal_error (input_location, "COLLECT_GCC must be set");
 
   const char *target_driver_name
     = DEFAULT_REAL_TARGET_MACHINE "-accel-" DEFAULT_TARGET_MACHINE "-gcc";
   char *target_compiler = find_target_compiler (target_driver_name);
   if (target_compiler == NULL)
-    fatal_error ("offload compiler %s not found", target_driver_name);
+    fatal_error (input_location, "offload compiler %s not found",
+		 target_driver_name);
 
   /* We may be called with all the arguments stored in some file and
      passed with @file.  Expand them into argv before processing.  */
@@ -500,7 +501,8 @@ main (int argc, char **argv)
 	if (strstr (argv[i], "ilp32"))
 	  target_ilp32 = true;
 	else if (!strstr (argv[i], "lp64"))
-	  fatal_error ("unrecognizable argument of option -foffload-abi");
+	  fatal_error (input_location,
+		       "unrecognizable argument of option -foffload-abi");
 	break;
       }
 
diff --git a/gcc/config/nios2/nios2.c b/gcc/config/nios2/nios2.c
index a7a140ee8d66378a7219f3bc8c22bbd206ec5c46..df33077947c00b6bb687cca62585c8f8b349dc66 100644
--- a/gcc/config/nios2/nios2.c
+++ b/gcc/config/nios2/nios2.c
@@ -885,7 +885,8 @@ nios2_custom_check_insns (void)
 		 "-fno-math-errno is specified", N2FPU_NAME (i));
 
   if (errors || custom_code_conflict)
-    fatal_error ("conflicting use of -mcustom switches, target attributes, "
+    fatal_error (input_location,
+		 "conflicting use of -mcustom switches, target attributes, "
 		 "and/or __builtin_custom_ functions");
 }
 
@@ -2562,7 +2563,8 @@ nios2_expand_fpu_builtin (tree exp, unsigned int code, rtx target)
   bool has_target_p = (dst_mode != VOIDmode);
 
   if (N2FPU_N (code) < 0)
-    fatal_error ("Cannot call %<__builtin_custom_%s%> without specifying switch"
+    fatal_error (input_location,
+		 "Cannot call %<__builtin_custom_%s%> without specifying switch"
 		 " %<-mcustom-%s%>", N2FPU_NAME (code), N2FPU_NAME (code));
   if (has_target_p)
     create_output_operand (&ops[opno++], target, dst_mode);
diff --git a/gcc/config/nvptx/mkoffload.c b/gcc/config/nvptx/mkoffload.c
index 9138bdd8dd893dcdd979464221165da6755a579e..38ccdba5de612ffd51de4cf187b5f7c0e5ba12ac 100644
--- a/gcc/config/nvptx/mkoffload.c
+++ b/gcc/config/nvptx/mkoffload.c
@@ -136,7 +136,7 @@ maybe_unlink (const char *file)
     {
       if (unlink_if_ordinary (file)
 	  && errno != ENOENT)
-	fatal_error ("deleting file %s: %m", file);
+	fatal_error (input_location, "deleting file %s: %m", file);
     }
   else
     fprintf (stderr, "[Leaving %s]\n", file);
@@ -163,7 +163,7 @@ record_id (const char *p1, id_map ***where)
 {
   const char *end = strchr (p1, '\n');
   if (!end)
-    fatal_error ("malformed ptx file");
+    fatal_error (input_location, "malformed ptx file");
 
   id_map *v = XNEW (id_map);
   size_t len = end - p1;
@@ -803,7 +803,8 @@ compile_native (const char *infile, const char *outfile, const char *compiler)
 {
   const char *collect_gcc_options = getenv ("COLLECT_GCC_OPTIONS");
   if (!collect_gcc_options)
-    fatal_error ("environment variable COLLECT_GCC_OPTIONS must be set");
+    fatal_error (input_location,
+		 "environment variable COLLECT_GCC_OPTIONS must be set");
 
   struct obstack argv_obstack;
   obstack_init (&argv_obstack);
@@ -828,7 +829,7 @@ main (int argc, char **argv)
 
   char *collect_gcc = getenv ("COLLECT_GCC");
   if (collect_gcc == NULL)
-    fatal_error ("COLLECT_GCC must be set.");
+    fatal_error (input_location, "COLLECT_GCC must be set.");
   const char *gcc_path = dirname (ASTRDUP (collect_gcc));
   const char *gcc_exec = basename (ASTRDUP (collect_gcc));
 
@@ -888,13 +889,13 @@ main (int argc, char **argv)
 
   in = fopen (ptx_name, "r");
   if (!in)
-    fatal_error ("cannot open intermediate ptx file");
+    fatal_error (input_location, "cannot open intermediate ptx file");
 
   ptx_cfile_name = make_temp_file (".c");
 
   out = fopen (ptx_cfile_name, "w");
   if (!out)
-    fatal_error ("cannot open '%s'", ptx_cfile_name);
+    fatal_error (input_location, "cannot open '%s'", ptx_cfile_name);
 
   process (in, out);
   fclose (out);
diff --git a/gcc/config/nvptx/nvptx.h b/gcc/config/nvptx/nvptx.h
index 3aa401b7453110cb384912cd1fc1091047afb4d3..9a9954bfed8adb617d86d75090d11916065361ac 100644
--- a/gcc/config/nvptx/nvptx.h
+++ b/gcc/config/nvptx/nvptx.h
@@ -185,7 +185,8 @@ struct nvptx_args {
 #define DEFAULT_PCC_STRUCT_RETURN 0
 
 #define FUNCTION_PROFILER(file, labelno) \
-  fatal_error ("profiling is not yet implemented for this architecture")
+  fatal_error (input_location, \
+	       "profiling is not yet implemented for this architecture")
 
 #define TRAMPOLINE_SIZE 32
 #define TRAMPOLINE_ALIGNMENT 256
diff --git a/gcc/config/rs6000/host-darwin.c b/gcc/config/rs6000/host-darwin.c
index 3a80316bf24dca18fb3045d79d6e3d9f1484d5ec..6361f5c23d772c37d1a323c74ca3554879bfcfe4 100644
--- a/gcc/config/rs6000/host-darwin.c
+++ b/gcc/config/rs6000/host-darwin.c
@@ -140,13 +140,13 @@ darwin_rs6000_extra_signals (void)
   sigstk.ss_size = SIGSTKSZ;
   sigstk.ss_flags = 0;
   if (sigaltstack (&sigstk, NULL) < 0)
-    fatal_error ("While setting up signal stack: %m");
+    fatal_error (input_location, "While setting up signal stack: %m");
 
   sigemptyset(&sact.sa_mask);
   sact.sa_flags = SA_ONSTACK | SA_SIGINFO;
   sact.sa_sigaction = segv_handler;
   if (sigaction (SIGSEGV, &sact, 0) < 0) 
-    fatal_error ("While setting up signal handler: %m");
+    fatal_error (input_location, "While setting up signal handler: %m");
 }
 
 
diff --git a/gcc/config/rs6000/rs6000.c b/gcc/config/rs6000/rs6000.c
index 40facd926f1f98088034758b59cdf78f2a4f137d..9bccf727fd22d1391edad4c2fc038801ef99bbce 100644
--- a/gcc/config/rs6000/rs6000.c
+++ b/gcc/config/rs6000/rs6000.c
@@ -11570,7 +11570,8 @@ def_builtin (const char *name, tree type, enum rs6000_builtins code)
   gcc_assert (IN_RANGE ((int)code, 0, (int)RS6000_BUILTIN_COUNT));
 
   if (rs6000_builtin_decls[(int)code])
-    fatal_error ("internal error: builtin function %s already processed", name);
+    fatal_error (input_location,
+		 "internal error: builtin function %s already processed", name);
 
   rs6000_builtin_decls[(int)code] = t =
     add_builtin_function (name, type, (int)code, BUILT_IN_MD, NULL, NULL_TREE);
@@ -15468,14 +15469,16 @@ builtin_function_type (machine_mode mode_ret, machine_mode mode_arg0,
     num_args--;
 
   if (num_args == 0)
-    fatal_error ("internal error: builtin function %s had no type", name);
+    fatal_error (input_location,
+		 "internal error: builtin function %s had no type", name);
 
   ret_type = builtin_mode_to_type[h.mode[0]][h.uns_p[0]];
   if (!ret_type && h.uns_p[0])
     ret_type = builtin_mode_to_type[h.mode[0]][0];
 
   if (!ret_type)
-    fatal_error ("internal error: builtin function %s had an unexpected "
+    fatal_error (input_location,
+		 "internal error: builtin function %s had an unexpected "
 		 "return type %s", name, GET_MODE_NAME (h.mode[0]));
 
   for (i = 0; i < (int) ARRAY_SIZE (arg_type); i++)
@@ -15491,7 +15494,8 @@ builtin_function_type (machine_mode mode_ret, machine_mode mode_arg0,
 	arg_type[i] = builtin_mode_to_type[m][0];
 
       if (!arg_type[i])
-	fatal_error ("internal error: builtin function %s, argument %d "
+	fatal_error (input_location,
+		     "internal error: builtin function %s, argument %d "
 		     "had unexpected argument type %s", name, i,
 		     GET_MODE_NAME (m));
     }
diff --git a/gcc/config/s390/s390.c b/gcc/config/s390/s390.c
index 1a3809d17bb60f784d9b7e5ce941a04deda4fff0..bc6223ecb4b94bae173079e96d268d38bb48ddbe 100644
--- a/gcc/config/s390/s390.c
+++ b/gcc/config/s390/s390.c
@@ -7810,7 +7810,8 @@ s390_frame_info (void)
 
   cfun_frame_layout.frame_size = get_frame_size ();
   if (!TARGET_64BIT && cfun_frame_layout.frame_size > 0x7fff0000)
-    fatal_error ("total size of local variables exceeds architecture limit");
+    fatal_error (input_location,
+		 "total size of local variables exceeds architecture limit");
 
   if (!TARGET_PACKED_STACK)
     {
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index 308e5bcc17f345d01b81281c995171e1ab743ac8..6cbb3f3730f157c95d5628bce6b0d2bad4a43bec 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,8 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* class.c, except.c, parser.c, pt.c: All callers of fatal_error
+	changed to pass input_location as first argument.
+
 2015-01-29  Jakub Jelinek  <jakub@redhat.com>
 
 	PR c++/64717
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index 1273064db3a8b44fbe394b79a29890c9f1191813..8612163711cf3e0708c702eb4f4c7a1e851c38b6 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -6792,7 +6792,8 @@ finish_struct (tree t, tree attributes)
 	    }
 	}
       if (!ok)
-	fatal_error ("definition of std::initializer_list does not match "
+	fatal_error (input_location,
+		     "definition of std::initializer_list does not match "
 		     "#include <initializer_list>");
     }
 
diff --git a/gcc/cp/except.c b/gcc/cp/except.c
index 902aeb228cb2e9319a1d40de4e1ae651ef79d3db..6aff7b594391431382c332058f350516211ed2f2 100644
--- a/gcc/cp/except.c
+++ b/gcc/cp/except.c
@@ -304,7 +304,8 @@ decl_is_java_type (tree decl, int err)
 
 	  if (jthrow_node == NULL_TREE)
 	    fatal_error
-	      ("call to Java %<catch%> or %<throw%> with %<jthrowable%> undefined");
+	      (input_location,
+	       "call to Java %<catch%> or %<throw%> with %<jthrowable%> undefined");
 
 	  jthrow_node = TREE_TYPE (TREE_TYPE (jthrow_node));
 
diff --git a/gcc/cp/parser.c b/gcc/cp/parser.c
index bfa3d81bf74f6e8df3338c85671f0c696651ba0c..7168aba358cfc62ec9e172305e2154bcf0d6691e 100644
--- a/gcc/cp/parser.c
+++ b/gcc/cp/parser.c
@@ -33165,7 +33165,8 @@ c_parse_file (void)
   static bool already_called = false;
 
   if (already_called)
-    fatal_error ("inter-module optimizations not implemented for C++");
+    fatal_error (input_location,
+		 "inter-module optimizations not implemented for C++");
   already_called = true;
 
   the_parser = cp_parser_new ();
diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index d377daaf2a62a5b57aa9a924817500cf92ab59d6..3317dad35d79d6cfba5fb90df6f5cc7fa895252c 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -8482,7 +8482,8 @@ push_tinst_level_loc (tree d, location_t loc)
 
   if (tinst_depth >= max_tinst_depth)
     {
-      fatal_error ("template instantiation depth exceeds maximum of %d"
+      fatal_error (input_location,
+		   "template instantiation depth exceeds maximum of %d"
                    " (use -ftemplate-depth= to increase the maximum)",
                    max_tinst_depth);
       return false;
@@ -20455,7 +20456,8 @@ instantiate_pending_templates (int retries)
     {
       tree decl = pending_templates->tinst->decl;
 
-      fatal_error ("template instantiation depth exceeds maximum of %d"
+      fatal_error (input_location,
+		   "template instantiation depth exceeds maximum of %d"
                    " instantiating %q+D, possibly from virtual table generation"
                    " (use -ftemplate-depth= to increase the maximum)",
                    max_tinst_depth, decl);
diff --git a/gcc/diagnostic-core.h b/gcc/diagnostic-core.h
index d97111dccacd5eeb477f9129ab3653c358b0b05d..09a6867c28a06d91b551c51bfe5a76afce5fd7d1 100644
--- a/gcc/diagnostic-core.h
+++ b/gcc/diagnostic-core.h
@@ -68,8 +68,6 @@ extern void error (const char *, ...) ATTRIBUTE_GCC_DIAG(1,2);
 extern void error_n (location_t, int, const char *, const char *, ...)
     ATTRIBUTE_GCC_DIAG(3,5) ATTRIBUTE_GCC_DIAG(4,5);
 extern void error_at (location_t, const char *, ...) ATTRIBUTE_GCC_DIAG(2,3);
-extern void fatal_error (const char *, ...) ATTRIBUTE_GCC_DIAG(1,2)
-     ATTRIBUTE_NORETURN;
 extern void fatal_error (location_t, const char *, ...) ATTRIBUTE_GCC_DIAG(2,3)
      ATTRIBUTE_NORETURN;
 /* Pass one of the OPT_W* from options.h as the second parameter.  */
diff --git a/gcc/diagnostic.c b/gcc/diagnostic.c
index 33eed3ec6f5fab3373e48ea067210f57716ed7a3..2196406f8814f6ff950c41c2610e0445a44a8e00 100644
--- a/gcc/diagnostic.c
+++ b/gcc/diagnostic.c
@@ -1191,23 +1191,6 @@ seen_error (void)
   return errorcount || sorrycount;
 }
 
-/* An error which is severe enough that we make no attempt to
-   continue.  Do not use this for internal consistency checks; that's
-   internal_error.  Use of this function should be rare.  */
-void
-fatal_error (const char *gmsgid, ...)
-{
-  diagnostic_info diagnostic;
-  va_list ap;
-
-  va_start (ap, gmsgid);
-  diagnostic_set_info (&diagnostic, gmsgid, &ap, input_location, DK_FATAL);
-  report_diagnostic (&diagnostic);
-  va_end (ap);
-
-  gcc_unreachable ();
-}
-
 /* An error which is severe enough that we make no attempt to
    continue.  Do not use this for internal consistency checks; that's
    internal_error.  Use of this function should be rare.  */
diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index c86b1a22237171252ecaea7f3e49a1518e535a2d..01462d2e312e2d0a27940cb6c290fdf858ce3d38 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,9 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* f95-lang.c, gfortranspec.c, trans-const.c, trans-expr.c: All
+	callers of fatal_error changed to pass input_location as first
+	argument.
+
 2015-01-28  Tobias Burnus  <burnus@net-b.de>
 
 	* intrinsic.texi (CO_BROADCAST): Correct argument description.
diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c
index 449f01aa8cf73750a45a7e18e94ff3ce9d59d61a..94f7479a22f0417c1a2c1b8dc2a6c260f08026f9 100644
--- a/gcc/fortran/f95-lang.c
+++ b/gcc/fortran/f95-lang.c
@@ -265,7 +265,7 @@ gfc_init (void)
   gfc_init_1 ();
 
   if (!gfc_new_file ())
-    fatal_error ("can't open input file: %s", gfc_source_file);
+    fatal_error (input_location, "can't open input file: %s", gfc_source_file);
 
   if (flag_preprocess_only)
     return false;
diff --git a/gcc/fortran/gfortranspec.c b/gcc/fortran/gfortranspec.c
index a5b3310666e47ed1a27c3bce0168af7b519377fc..8af4c768035c5e7dc3b6ede846576723eed10aa7 100644
--- a/gcc/fortran/gfortranspec.c
+++ b/gcc/fortran/gfortranspec.c
@@ -142,7 +142,7 @@ append_arg (const struct cl_decoded_option *arg)
     }
 
   if (g77_newargc == newargsize)
-    fatal_error ("overflowed output arg list for %qs",
+    fatal_error (input_location, "overflowed output arg list for %qs",
 		 arg->orig_option_with_args_text);
 
   g77_new_decoded_options[g77_newargc++] = *arg;
@@ -296,7 +296,8 @@ For more information about these matters, see the file named COPYING\n\n"));
     }
 
   if ((n_outfiles != 0) && (n_infiles == 0))
-    fatal_error ("no input files; unwilling to write output files");
+    fatal_error (input_location,
+		 "no input files; unwilling to write output files");
 
   /* If there are no input files, no need for the library.  */
   if (n_infiles == 0)
diff --git a/gcc/fortran/trans-const.c b/gcc/fortran/trans-const.c
index 4e2f577181b40d4ee37106507ebd56845e455161..eb447a5d761314a09715c9fa552685c94cba9d38 100644
--- a/gcc/fortran/trans-const.c
+++ b/gcc/fortran/trans-const.c
@@ -368,7 +368,8 @@ gfc_conv_constant_to_tree (gfc_expr * expr)
 				     expr->representation.string);
 
     default:
-      fatal_error ("gfc_conv_constant_to_tree(): invalid type: %s",
+      fatal_error (input_location,
+		   "gfc_conv_constant_to_tree(): invalid type: %s",
 		   gfc_typename (&expr->ts));
     }
 }
diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 91cac41f9990818465c0d30a8c67746404dec403..70da287dae47f721a4863815715460a9f798defd 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -2859,7 +2859,7 @@ gfc_conv_expr_op (gfc_se * se, gfc_expr * expr)
       gcc_unreachable ();
 
     default:
-      fatal_error ("Unknown intrinsic op");
+      fatal_error (input_location, "Unknown intrinsic op");
       return;
     }
 
diff --git a/gcc/gcc.c b/gcc/gcc.c
index f682c3b07122bd44343ef7dd7bb4508f72467342..186f0aef91b9d7a58f5a793f564cf085cde7eddd 100644
--- a/gcc/gcc.c
+++ b/gcc/gcc.c
@@ -1896,7 +1896,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		p1++;
 
 	      if (*p1++ != '<' || p[-2] != '>')
-		fatal_error ("specs %%include syntax malformed after "
+		fatal_error (input_location,
+			     "specs %%include syntax malformed after "
 			     "%ld characters",
 			     (long) (p1 - buffer + 1));
 
@@ -1916,7 +1917,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		p1++;
 
 	      if (*p1++ != '<' || p[-2] != '>')
-		fatal_error ("specs %%include syntax malformed after "
+		fatal_error (input_location,
+			     "specs %%include syntax malformed after "
 			     "%ld characters",
 			     (long) (p1 - buffer + 1));
 
@@ -1942,7 +1944,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		p1++;
 
 	      if (! ISALPHA ((unsigned char) *p1))
-		fatal_error ("specs %%rename syntax malformed after "
+		fatal_error (input_location,
+			     "specs %%rename syntax malformed after "
 			     "%ld characters",
 			     (long) (p1 - buffer));
 
@@ -1951,7 +1954,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		p2++;
 
 	      if (*p2 != ' ' && *p2 != '\t')
-		fatal_error ("specs %%rename syntax malformed after "
+		fatal_error (input_location,
+			     "specs %%rename syntax malformed after "
 			     "%ld characters",
 			     (long) (p2 - buffer));
 
@@ -1961,7 +1965,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		p2++;
 
 	      if (! ISALPHA ((unsigned char) *p2))
-		fatal_error ("specs %%rename syntax malformed after "
+		fatal_error (input_location,
+			     "specs %%rename syntax malformed after "
 			     "%ld characters",
 			     (long) (p2 - buffer));
 
@@ -1971,7 +1976,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		p3++;
 
 	      if (p3 != p - 1)
-		fatal_error ("specs %%rename syntax malformed after "
+		fatal_error (input_location,
+			     "specs %%rename syntax malformed after "
 			     "%ld characters",
 			     (long) (p3 - buffer));
 	      *p3 = '\0';
@@ -1981,14 +1987,16 @@ read_specs (const char *filename, bool main_p, bool user_p)
 		  break;
 
 	      if (!sl)
-		fatal_error ("specs %s spec was not found to be renamed", p1);
+		fatal_error (input_location,
+			     "specs %s spec was not found to be renamed", p1);
 
 	      if (strcmp (p1, p2) == 0)
 		continue;
 
 	      for (newsl = specs; newsl; newsl = newsl->next)
 		if (strcmp (newsl->name, p2) == 0)
-		  fatal_error ("%s: attempt to rename spec %qs to "
+		  fatal_error (input_location,
+			       "%s: attempt to rename spec %qs to "
 			       "already defined spec %qs",
 		    filename, p1, p2);
 
@@ -2009,7 +2017,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 	      continue;
 	    }
 	  else
-	    fatal_error ("specs unknown %% command after %ld characters",
+	    fatal_error (input_location,
+			 "specs unknown %% command after %ld characters",
 			 (long) (p1 - buffer));
 	}
 
@@ -2020,7 +2029,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
 
       /* The colon shouldn't be missing.  */
       if (*p1 != ':')
-	fatal_error ("specs file malformed after %ld characters",
+	fatal_error (input_location,
+		     "specs file malformed after %ld characters",
 		     (long) (p1 - buffer));
 
       /* Skip back over trailing whitespace.  */
@@ -2033,7 +2043,8 @@ read_specs (const char *filename, bool main_p, bool user_p)
       /* Find the next line.  */
       p = skip_whitespace (p1 + 1);
       if (p[1] == 0)
-	fatal_error ("specs file malformed after %ld characters",
+	fatal_error (input_location,
+		     "specs file malformed after %ld characters",
 		     (long) (p - buffer));
 
       p1 = p;
@@ -2085,7 +2096,7 @@ read_specs (const char *filename, bool main_p, bool user_p)
     }
 
   if (link_command_spec == 0)
-    fatal_error ("spec file has no spec for linking");
+    fatal_error (input_location, "spec file has no spec for linking");
 }
 
 /* Record the names of temporary files we tell compilers to write,
@@ -2630,7 +2641,7 @@ add_sysrooted_prefix (struct path_prefix *pprefix, const char *prefix,
 		      int require_machine_suffix, int os_multilib)
 {
   if (!IS_ABSOLUTE_PATH (prefix))
-    fatal_error ("system path %qs is not absolute", prefix);
+    fatal_error (input_location, "system path %qs is not absolute", prefix);
 
   if (target_system_root)
     {
@@ -2718,7 +2729,7 @@ execute (void)
     if (arg && strcmp (arg, "|") == 0)
       {				/* each command.  */
 #if defined (__MSDOS__) || defined (OS2) || defined (VMS)
-	fatal_error ("-pipe not supported");
+	fatal_error (input_location, "-pipe not supported");
 #endif
 	argbuf[i] = 0; /* Termination of
 						     command args.  */
@@ -2841,7 +2852,7 @@ execute (void)
 				   ? PEX_RECORD_TIMES : 0),
 		  progname, temp_filename);
   if (pex == NULL)
-    fatal_error ("pex_init failed: %m");
+    fatal_error (input_location, "pex_init failed: %m");
 
   for (i = 0; i < n_commands; i++)
     {
@@ -2857,7 +2868,7 @@ execute (void)
       if (errmsg != NULL)
 	{
 	  if (err == 0)
-	    fatal_error (errmsg);
+	    fatal_error (input_location, errmsg);
 	  else
 	    {
 	      errno = err;
@@ -2880,13 +2891,13 @@ execute (void)
 
     statuses = (int *) alloca (n_commands * sizeof (int));
     if (!pex_get_status (pex, n_commands, statuses))
-      fatal_error ("failed to get exit status: %m");
+      fatal_error (input_location, "failed to get exit status: %m");
 
     if (report_times || report_times_to_file)
       {
 	times = (struct pex_time *) alloca (n_commands * sizeof (struct pex_time));
 	if (!pex_get_times (pex, n_commands, times))
-	  fatal_error ("failed to get process times: %m");
+	  fatal_error (input_location, "failed to get process times: %m");
       }
 
     pex_free (pex);
@@ -3420,7 +3431,8 @@ handle_foffload_option (const char *arg)
 	}
 
       if (!c)
-	fatal_error ("GCC is not configured to support %s as offload target",
+	fatal_error (input_location,
+		     "GCC is not configured to support %s as offload target",
 		     target);
 
       if (!offload_targets)
@@ -3719,7 +3731,7 @@ driver_handle_option (struct gcc_options *opts,
 	       || strcmp (arg, "object") == 0)
 	save_temps_flag = SAVE_TEMPS_OBJ;
       else
-	fatal_error ("%qs is an unknown -save-temps option",
+	fatal_error (input_location, "%qs is an unknown -save-temps option",
 		     decoded->orig_option_with_args_text);
       break;
 
@@ -4174,7 +4186,8 @@ process_command (unsigned int decoded_options_count,
       for (i = 0; i < n_infiles; i++)
 	if ((!infiles[i].language || infiles[i].language[0] != '*')
 	    && canonical_filename_eq (infiles[i].name, output_file))
-	  fatal_error ("input file %qs is the same as output file",
+	  fatal_error (input_location,
+		       "input file %qs is the same as output file",
 		       output_file);
     }
 
@@ -4655,10 +4668,12 @@ do_self_spec (const char *spec)
 	      /* Specs should only generate options, not input
 		 files.  */
 	      if (strcmp (decoded_options[j].arg, "-") != 0)
-		fatal_error ("switch %qs does not start with %<-%>",
+		fatal_error (input_location,
+			     "switch %qs does not start with %<-%>",
 			     decoded_options[j].arg);
 	      else
-		fatal_error ("spec-generated switch is just %<-%>");
+		fatal_error (input_location,
+			     "spec-generated switch is just %<-%>");
 	      break;
 
 	    case OPT_fcompare_debug_second:
@@ -4749,19 +4764,20 @@ create_at_file (char **argv)
   int status;
 
   if (f == NULL)
-    fatal_error ("could not open temporary response file %s",
+    fatal_error (input_location, "could not open temporary response file %s",
 		 temp_file);
 
   status = writeargv (argv, f);
 
   if (status)
-    fatal_error ("could not write to temporary response file %s",
+    fatal_error (input_location,
+		 "could not write to temporary response file %s",
 		 temp_file);
 
   status = fclose (f);
 
   if (EOF == status)
-    fatal_error ("could not close temporary response file %s",
+    fatal_error (input_location, "could not close temporary response file %s",
 		 temp_file);
 
   store_arg (at_argument, 0, 0);
@@ -4884,7 +4900,7 @@ do_spec_1 (const char *spec, int inswitch, const char *soft_matched_part)
 	switch (c = *p++)
 	  {
 	  case 0:
-	    fatal_error ("spec %qs invalid", spec);
+	    fatal_error (input_location, "spec %qs invalid", spec);
 
 	  case 'b':
 	    if (save_temps_length)
@@ -5033,7 +5049,8 @@ do_spec_1 (const char *spec, int inswitch, const char *soft_matched_part)
 		    p += 2;
 		    /* We don't support extra suffix characters after %O.  */
 		    if (*p == '.' || ISALNUM ((unsigned char) *p))
-		      fatal_error ("spec %qs has invalid %<%%0%c%>", spec, *p);
+		      fatal_error (input_location,
+				   "spec %qs has invalid %<%%0%c%>", spec, *p);
 		    if (suffix_length == 0)
 		      suffix = TARGET_OBJECT_SUFFIX;
 		    else
@@ -5352,7 +5369,8 @@ do_spec_1 (const char *spec, int inswitch, const char *soft_matched_part)
 	      unsigned int cur_index = argbuf.length ();
 	      /* Handle the {...} following the %W.  */
 	      if (*p != '{')
-		fatal_error ("spec %qs has invalid %<%%W%c%>", spec, *p);
+		fatal_error (input_location,
+			     "spec %qs has invalid %<%%W%c%>", spec, *p);
 	      p = handle_braces (p + 1);
 	      if (p == 0)
 		return -1;
@@ -5374,7 +5392,8 @@ do_spec_1 (const char *spec, int inswitch, const char *soft_matched_part)
 
 	      /* Skip past the option value and make a copy.  */
 	      if (*p != '{')
-		fatal_error ("spec %qs has invalid %<%%x%c%>", spec, *p);
+		fatal_error (input_location,
+			     "spec %qs has invalid %<%%x%c%>", spec, *p);
 	      while (*p++ != '}')
 		;
 	      string = save_string (p1 + 1, p - p1 - 2);
@@ -5690,7 +5709,7 @@ eval_spec_function (const char *func, const char *args)
 
   sf = lookup_spec_function (func);
   if (sf == NULL)
-    fatal_error ("unknown spec function %qs", func);
+    fatal_error (input_location, "unknown spec function %qs", func);
 
   /* Push the spec processing context.  */
   save_argbuf = argbuf;
@@ -5720,7 +5739,7 @@ eval_spec_function (const char *func, const char *args)
 
   alloc_args ();
   if (do_spec_2 (args) < 0)
-    fatal_error ("error in args to spec function %qs", func);
+    fatal_error (input_location, "error in args to spec function %qs", func);
 
   /* argbuf_index is an index for the next argument to be inserted, and
      so contains the count of the args already inserted.  */
@@ -5774,10 +5793,10 @@ handle_spec_function (const char *p, bool *retval_nonnull)
         break;
       /* Only allow [A-Za-z0-9], -, and _ in function names.  */
       if (!ISALNUM (*endp) && !(*endp == '-' || *endp == '_'))
-	fatal_error ("malformed spec function name");
+	fatal_error (input_location, "malformed spec function name");
     }
   if (*endp != '(')		/* ) */
-    fatal_error ("no arguments for spec function");
+    fatal_error (input_location, "no arguments for spec function");
   func = save_string (p, endp - p);
   p = ++endp;
 
@@ -5796,7 +5815,7 @@ handle_spec_function (const char *p, bool *retval_nonnull)
     }
   /* ( */
   if (*endp != ')')
-    fatal_error ("malformed spec function arguments");
+    fatal_error (input_location, "malformed spec function arguments");
   args = save_string (p, endp - p);
   p = ++endp;
 
@@ -6070,7 +6089,7 @@ handle_braces (const char *p)
   return p;
 
  invalid:
-  fatal_error ("braced spec %qs is invalid at %qc", orig, *p);
+  fatal_error (input_location, "braced spec %qs is invalid at %qc", orig, *p);
 
 #undef SKIP_WHITE
 }
@@ -6158,7 +6177,7 @@ process_brace_body (const char *p, const char *atom, const char *end_atom,
   return p;
 
  invalid:
-  fatal_error ("braced spec body %qs is invalid", body);
+  fatal_error (input_location, "braced spec body %qs is invalid", body);
 }
 
 /* Return 0 iff switch number SWITCHNUM is obsoleted by a later switch
@@ -6454,7 +6473,7 @@ run_attempt (const char **new_argv, const char *out_temp,
 
   pex = pex_init (PEX_USE_PIPES, new_argv[0], NULL);
   if (!pex)
-    fatal_error ("pex_init failed: %m");
+    fatal_error (input_location, "pex_init failed: %m");
 
   errmsg = pex_run (pex, pex_flags, new_argv[0],
 		    CONST_CAST2 (char *const *, const char **, &new_argv[1]), out_temp,
@@ -6462,7 +6481,7 @@ run_attempt (const char **new_argv, const char *out_temp,
   if (errmsg != NULL)
     {
       if (err == 0)
-	fatal_error (errmsg);
+	fatal_error (input_location, errmsg);
       else
 	{
 	  errno = err;
@@ -7003,7 +7022,7 @@ driver::global_initializations ()
 #endif
 
   if (atexit (delete_temp_files) != 0)
-    fatal_error ("atexit failed");
+    fatal_error (input_location, "atexit failed");
 
   if (signal (SIGINT, SIG_IGN) != SIG_IGN)
     signal (SIGINT, fatal_signal);
@@ -7527,7 +7546,8 @@ driver::maybe_print_and_exit () const
       else
 	/* The error status indicates that only one set of fixed
 	   headers should be built.  */
-	fatal_error ("not configured with sysroot headers suffix");
+	fatal_error (input_location,
+		     "not configured with sysroot headers suffix");
     }
 
   if (print_help_list)
@@ -7588,7 +7608,7 @@ driver::prepare_infiles ()
   int lang_n_infiles = 0;
 
   if (n_infiles == added_libraries)
-    fatal_error ("no input files");
+    fatal_error (input_location, "no input files");
 
   if (seen_error ())
     /* Early exit needed from main.  */
@@ -7638,7 +7658,8 @@ driver::prepare_infiles ()
     }
 
   if (!combine_inputs && have_c && have_o && lang_n_infiles > 1)
-    fatal_error ("cannot specify -o with -c, -S or -E with multiple files");
+    fatal_error (input_location,
+		 "cannot specify -o with -c, -S or -E with multiple files");
 
   /* No early exit needed from main; we can continue.  */
   return false;
@@ -7844,7 +7865,8 @@ driver::maybe_run_linker (const char *argv0) const
 					     LTOPLUGINSONAME, R_OK,
 					     false);
 	      if (!temp_spec)
-		fatal_error ("-fuse-linker-plugin, but %s not found",
+		fatal_error (input_location,
+			     "-fuse-linker-plugin, but %s not found",
 			     LTOPLUGINSONAME);
 	      linker_plugin_file_spec = convert_white_space (temp_spec);
 	    }
@@ -8156,7 +8178,7 @@ used_arg (const char *p, int len)
 	      if (*q == '\0')
 		{
 		invalid_matches:
-		  fatal_error ("multilib spec %qs is invalid",
+		  fatal_error (input_location, "multilib spec %qs is invalid",
 			       multilib_matches);
 		}
 	      q++;
@@ -8350,7 +8372,7 @@ set_multilib_dir (void)
 	  if (*p == '\0')
 	    {
 	    invalid_exclusions:
-	      fatal_error ("multilib exclusions %qs is invalid",
+	      fatal_error (input_location, "multilib exclusions %qs is invalid",
 			   multilib_exclusions);
 	    }
 
@@ -8414,7 +8436,7 @@ set_multilib_dir (void)
 	  if (*p == '\0')
 	    {
 	    invalid_select:
-	      fatal_error ("multilib select %qs %qs is invalid",
+	      fatal_error (input_location, "multilib select %qs %qs is invalid",
 			   multilib_select, multilib_reuse);
 	    }
 	  ++p;
@@ -8575,7 +8597,8 @@ print_multilib_info (void)
 	  if (*p == '\0')
 	    {
 	    invalid_select:
-	      fatal_error ("multilib select %qs is invalid", multilib_select);
+	      fatal_error (input_location,
+			   "multilib select %qs is invalid", multilib_select);
 	    }
 
 	  ++p;
@@ -8614,7 +8637,8 @@ print_multilib_info (void)
 		if (*e == '\0')
 		  {
 		  invalid_exclusion:
-		    fatal_error ("multilib exclusion %qs is invalid",
+		    fatal_error (input_location,
+				 "multilib exclusion %qs is invalid",
 				 multilib_exclusions);
 		  }
 
@@ -8820,7 +8844,8 @@ getenv_spec_function (int argc, const char **argv)
 
   value = getenv (argv[0]);
   if (!value)
-    fatal_error ("environment variable %qs not defined", argv[0]);
+    fatal_error (input_location,
+		 "environment variable %qs not defined", argv[0]);
 
   /* We have to escape every character of the environment variable so
      they are not interpreted as active spec characters.  A
@@ -8959,12 +8984,12 @@ compare_version_strings (const char *v1, const char *v2)
     abort ();
   rresult = regexec (&r, v1, 0, NULL, 0);
   if (rresult == REG_NOMATCH)
-    fatal_error ("invalid version number %qs", v1);
+    fatal_error (input_location, "invalid version number %qs", v1);
   else if (rresult != 0)
     abort ();
   rresult = regexec (&r, v2, 0, NULL, 0);
   if (rresult == REG_NOMATCH)
-    fatal_error ("invalid version number %qs", v2);
+    fatal_error (input_location, "invalid version number %qs", v2);
   else if (rresult != 0)
     abort ();
 
@@ -9007,13 +9032,13 @@ version_compare_spec_function (int argc, const char **argv)
   bool result;
 
   if (argc < 3)
-    fatal_error ("too few arguments to %%:version-compare");
+    fatal_error (input_location, "too few arguments to %%:version-compare");
   if (argv[0][0] == '\0')
     abort ();
   if ((argv[0][1] == '<' || argv[0][1] == '>') && argv[0][0] != '!')
     nargs = 2;
   if (argc != nargs + 3)
-    fatal_error ("too many arguments to %%:version-compare");
+    fatal_error (input_location, "too many arguments to %%:version-compare");
 
   switch_len = strlen (argv[nargs + 1]);
   for (i = 0; i < n_switches; i++)
@@ -9054,7 +9079,8 @@ version_compare_spec_function (int argc, const char **argv)
       break;
 
     default:
-      fatal_error ("unknown operator %qs in %%:version-compare", argv[0]);
+      fatal_error (input_location,
+		   "unknown operator %qs in %%:version-compare", argv[0]);
     }
   if (! result)
     return NULL;
@@ -9177,7 +9203,8 @@ compare_debug_dump_opt_spec_function (int arg,
   static char random_seed[HOST_BITS_PER_WIDE_INT / 4 + 3];
 
   if (arg != 0)
-    fatal_error ("too many arguments to %%:compare-debug-dump-opt");
+    fatal_error (input_location,
+		 "too many arguments to %%:compare-debug-dump-opt");
 
   do_spec_2 ("%{fdump-final-insns=*:%*}");
   do_spec_1 (" ", 0, NULL);
@@ -9249,7 +9276,8 @@ compare_debug_self_opt_spec_function (int arg,
 				      const char **argv ATTRIBUTE_UNUSED)
 {
   if (arg != 0)
-    fatal_error ("too many arguments to %%:compare-debug-self-opt");
+    fatal_error (input_location,
+		 "too many arguments to %%:compare-debug-self-opt");
 
   if (compare_debug >= 0)
     return NULL;
@@ -9284,17 +9312,19 @@ compare_debug_auxbase_opt_spec_function (int arg,
   int len;
 
   if (arg == 0)
-    fatal_error ("too few arguments to %%:compare-debug-auxbase-opt");
+    fatal_error (input_location,
+		 "too few arguments to %%:compare-debug-auxbase-opt");
 
   if (arg != 1)
-    fatal_error ("too many arguments to %%:compare-debug-auxbase-opt");
+    fatal_error (input_location,
+		 "too many arguments to %%:compare-debug-auxbase-opt");
 
   if (compare_debug >= 0)
     return NULL;
 
   len = strlen (argv[0]);
   if (len < 3 || strcmp (argv[0] + len - 3, ".gk") != 0)
-    fatal_error ("argument to %%:compare-debug-auxbase-opt "
+    fatal_error (input_location, "argument to %%:compare-debug-auxbase-opt "
 		 "does not end in .gk");
 
   if (debug_auxbase_opt)
@@ -9368,7 +9398,7 @@ replace_extension_spec_func (int argc, const char **argv)
   int i;
 
   if (argc != 2)
-    fatal_error ("too few arguments to %%:replace-extension");
+    fatal_error (input_location, "too few arguments to %%:replace-extension");
 
   name = xstrdup (argv[0]);
 
diff --git a/gcc/gcov-io.h b/gcc/gcov-io.h
index 64ee85a2fd41fbedc2fb9139adb3ced101e89fb3..dcb29441f61e85e23005c1ef2808a0a86de3dfaf 100644
--- a/gcc/gcov-io.h
+++ b/gcc/gcov-io.h
@@ -199,7 +199,7 @@ typedef uint64_t gcov_type_unsigned;
 #define gcov_nonruntime_assert(EXPR) ((void)(0 && (EXPR)))
 #else
 #define gcov_nonruntime_assert(EXPR) gcc_assert (EXPR)
-#define gcov_error(...) fatal_error (__VA_ARGS__)
+#define gcov_error(...) fatal_error (input_location, __VA_ARGS__)
 #endif
 
 /* File suffixes.  */
diff --git a/gcc/gcov-tool.c b/gcc/gcov-tool.c
index 7de175fdfcc3ed1aced5a5486ca3f5f56aca469c..0f97b532d7f34234d1295ef984a873611b5c4498 100644
--- a/gcc/gcov-tool.c
+++ b/gcc/gcov-tool.c
@@ -65,7 +65,7 @@ unlink_gcda_file (const char *name,
     ret = remove (name);
 
   if (ret)
-    fatal_error ("error in removing %s\n", name);
+    fatal_error (input_location, "error in removing %s\n", name);
 
   return ret;
 }
@@ -95,7 +95,7 @@ gcov_output_files (const char *out, struct gcov_info *profile)
 #else
       if (mkdir (out) == -1 && errno != EEXIST)
 #endif
-        fatal_error ("Cannot make directory %s", out);
+        fatal_error (input_location, "Cannot make directory %s", out);
     } else
       unlink_profile_dir (out);
 
@@ -103,17 +103,17 @@ gcov_output_files (const char *out, struct gcov_info *profile)
   pwd = getcwd (NULL, 0);
 
   if (pwd == NULL)
-    fatal_error ("Cannot get current directory name");
+    fatal_error (input_location, "Cannot get current directory name");
 
   ret = chdir (out);
   if (ret)
-    fatal_error ("Cannot change directory to %s", out);
+    fatal_error (input_location, "Cannot change directory to %s", out);
 
   gcov_do_dump (profile, 0);
 
   ret = chdir (pwd);
   if (ret)
-    fatal_error ("Cannot change directory to %s", pwd);
+    fatal_error (input_location, "Cannot change directory to %s", pwd);
 
   free (pwd);
 }
@@ -207,7 +207,7 @@ do_merge (int argc, char **argv)
         case 'w':
           sscanf (optarg, "%d,%d", &w1, &w2);
           if (w1 < 0 || w2 < 0)
-            fatal_error ("weights need to be non-negative\n");
+            fatal_error (input_location, "weights need to be non-negative\n");
           break;
         default:
           merge_usage ();
@@ -350,7 +350,7 @@ do_rewrite (int argc, char **argv)
             }
 
           if (scale < 0.0)
-            fatal_error ("scale needs to be non-negative\n");
+            fatal_error (input_location, "scale needs to be non-negative\n");
 
           if (normalize_val != 0)
             {
diff --git a/gcc/ggc-common.c b/gcc/ggc-common.c
index 524e85e42422f402d40d0d1b950db481b856cba2..03fbe7d80cf3ec8db3033cd12560862711c93e8d 100644
--- a/gcc/ggc-common.c
+++ b/gcc/ggc-common.c
@@ -395,7 +395,7 @@ write_pch_globals (const struct ggc_root_tab * const *tab,
 	    {
 	      if (fwrite (&ptr, sizeof (void *), 1, state->f)
 		  != 1)
-		fatal_error ("can%'t write PCH file: %m");
+		fatal_error (input_location, "can%'t write PCH file: %m");
 	    }
 	  else
 	    {
@@ -403,7 +403,7 @@ write_pch_globals (const struct ggc_root_tab * const *tab,
 		saving_htab->find_with_hash (ptr, POINTER_HASH (ptr));
 	      if (fwrite (&new_ptr->new_addr, sizeof (void *), 1, state->f)
 		  != 1)
-		fatal_error ("can%'t write PCH file: %m");
+		fatal_error (input_location, "can%'t write PCH file: %m");
 	    }
 	}
 }
@@ -472,7 +472,7 @@ gt_pch_save (FILE *f)
   for (rt = gt_pch_scalar_rtab; *rt; rt++)
     for (rti = *rt; rti->base != NULL; rti++)
       if (fwrite (rti->base, rti->stride, 1, f) != 1)
-	fatal_error ("can%'t write PCH file: %m");
+	fatal_error (input_location, "can%'t write PCH file: %m");
 
   /* Write out all the global pointers, after translation.  */
   write_pch_globals (gt_ggc_rtab, &state);
@@ -483,17 +483,17 @@ gt_pch_save (FILE *f)
     long o;
     o = ftell (state.f) + sizeof (mmi);
     if (o == -1)
-      fatal_error ("can%'t get position in PCH file: %m");
+      fatal_error (input_location, "can%'t get position in PCH file: %m");
     mmi.offset = mmap_offset_alignment - o % mmap_offset_alignment;
     if (mmi.offset == mmap_offset_alignment)
       mmi.offset = 0;
     mmi.offset += o;
   }
   if (fwrite (&mmi, sizeof (mmi), 1, state.f) != 1)
-    fatal_error ("can%'t write PCH file: %m");
+    fatal_error (input_location, "can%'t write PCH file: %m");
   if (mmi.offset != 0
       && fseek (state.f, mmi.offset, SEEK_SET) != 0)
-    fatal_error ("can%'t write padding to PCH file: %m");
+    fatal_error (input_location, "can%'t write padding to PCH file: %m");
 
   ggc_pch_prepare_write (state.d, state.f);
 
@@ -615,7 +615,7 @@ gt_pch_restore (FILE *f)
   for (rt = gt_pch_scalar_rtab; *rt; rt++)
     for (rti = *rt; rti->base != NULL; rti++)
       if (fread (rti->base, rti->stride, 1, f) != 1)
-	fatal_error ("can%'t read PCH file: %m");
+	fatal_error (input_location, "can%'t read PCH file: %m");
 
   /* Read in all the global pointers, in 6 easy loops.  */
   for (rt = gt_ggc_rtab; *rt; rt++)
@@ -623,23 +623,23 @@ gt_pch_restore (FILE *f)
       for (i = 0; i < rti->nelt; i++)
 	if (fread ((char *)rti->base + rti->stride * i,
 		   sizeof (void *), 1, f) != 1)
-	  fatal_error ("can%'t read PCH file: %m");
+	  fatal_error (input_location, "can%'t read PCH file: %m");
 
   if (fread (&mmi, sizeof (mmi), 1, f) != 1)
-    fatal_error ("can%'t read PCH file: %m");
+    fatal_error (input_location, "can%'t read PCH file: %m");
 
   result = host_hooks.gt_pch_use_address (mmi.preferred_base, mmi.size,
 					  fileno (f), mmi.offset);
   if (result < 0)
-    fatal_error ("had to relocate PCH");
+    fatal_error (input_location, "had to relocate PCH");
   if (result == 0)
     {
       if (fseek (f, mmi.offset, SEEK_SET) != 0
 	  || fread (mmi.preferred_base, mmi.size, 1, f) != 1)
-	fatal_error ("can%'t read PCH file: %m");
+	fatal_error (input_location, "can%'t read PCH file: %m");
     }
   else if (fseek (f, mmi.offset + mmi.size, SEEK_SET) != 0)
-    fatal_error ("can%'t read PCH file: %m");
+    fatal_error (input_location, "can%'t read PCH file: %m");
 
   ggc_pch_read (f, mmi.preferred_base);
 
diff --git a/gcc/ggc-page.c b/gcc/ggc-page.c
index e70c0ea4d2d767eb2ee263e20ecc2b52de7f1649..158156a37b5368cfc4a037b05dc8a10693628519 100644
--- a/gcc/ggc-page.c
+++ b/gcc/ggc-page.c
@@ -2449,7 +2449,7 @@ ggc_pch_write_object (struct ggc_pch_data *d,
     }
 
   if (fwrite (x, size, 1, f) != 1)
-    fatal_error ("can%'t write PCH file: %m");
+    fatal_error (input_location, "can%'t write PCH file: %m");
 
   /* If SIZE is not the same as OBJECT_SIZE(order), then we need to pad the
      object out to OBJECT_SIZE(order).  This happens for strings.  */
@@ -2465,13 +2465,13 @@ ggc_pch_write_object (struct ggc_pch_data *d,
       if (padding <= sizeof (emptyBytes))
         {
           if (fwrite (emptyBytes, 1, padding, f) != padding)
-            fatal_error ("can%'t write PCH file");
+            fatal_error (input_location, "can%'t write PCH file");
         }
       else
         {
           /* Larger than our buffer?  Just default to fseek.  */
           if (fseek (f, padding, SEEK_CUR) != 0)
-            fatal_error ("can%'t write PCH file");
+            fatal_error (input_location, "can%'t write PCH file");
         }
     }
 
@@ -2480,14 +2480,14 @@ ggc_pch_write_object (struct ggc_pch_data *d,
       && fseek (f, ROUND_UP_VALUE (d->d.totals[order] * OBJECT_SIZE (order),
 				   G.pagesize),
 		SEEK_CUR) != 0)
-    fatal_error ("can%'t write PCH file: %m");
+    fatal_error (input_location, "can%'t write PCH file: %m");
 }
 
 void
 ggc_pch_finish (struct ggc_pch_data *d, FILE *f)
 {
   if (fwrite (&d->d, sizeof (d->d), 1, f) != 1)
-    fatal_error ("can%'t write PCH file: %m");
+    fatal_error (input_location, "can%'t write PCH file: %m");
   free (d);
 }
 
@@ -2577,7 +2577,7 @@ ggc_pch_read (FILE *f, void *addr)
   /* Allocate the appropriate page-table entries for the pages read from
      the PCH file.  */
   if (fread (&d, sizeof (d), 1, f) != 1)
-    fatal_error ("can%'t read PCH file: %m");
+    fatal_error (input_location, "can%'t read PCH file: %m");
 
   for (i = 0; i < NUM_ORDERS; i++)
     {
diff --git a/gcc/graph.c b/gcc/graph.c
index 91e39442d7c88b0dccd007bfa8ee036198e1ad4a..a1eb24c49ccb99faba3201a9068cd3dceaf9d194 100644
--- a/gcc/graph.c
+++ b/gcc/graph.c
@@ -63,7 +63,7 @@ open_graph_file (const char *base, const char *mode)
 
   fp = fopen (buf, mode);
   if (fp == NULL)
-    fatal_error ("can%'t open %s: %m", buf);
+    fatal_error (input_location, "can%'t open %s: %m", buf);
 
   return fp;
 }
diff --git a/gcc/ipa-inline-analysis.c b/gcc/ipa-inline-analysis.c
index 02b756e8566556a9d0f87913a11a582149d54f35..ffa559c0c5f22b74a7f179fb53af7aabe2ada8bb 100644
--- a/gcc/ipa-inline-analysis.c
+++ b/gcc/ipa-inline-analysis.c
@@ -4251,7 +4251,8 @@ inline_read_summary (void)
 	/* Fatal error here.  We do not want to support compiling ltrans units
 	   with different version of compiler or different flags than the WPA
 	   unit, so this should never happen.  */
-	fatal_error ("ipa inline summary is missing in input file");
+	fatal_error (input_location,
+		     "ipa inline summary is missing in input file");
     }
   if (optimize)
     {
diff --git a/gcc/ipa-reference.c b/gcc/ipa-reference.c
index 5f43a02a1e182b71f7c14befd11e0d4a6f4c127e..219a9b3828d09ace1b760016176370412f74585f 100644
--- a/gcc/ipa-reference.c
+++ b/gcc/ipa-reference.c
@@ -1172,7 +1172,8 @@ ipa_reference_read_optimization_summary (void)
 	/* Fatal error here.  We do not want to support compiling ltrans units with
 	   different version of compiler or different flags than the WPA unit, so
 	   this should never happen.  */
-	fatal_error ("ipa reference summary is missing in ltrans unit");
+	fatal_error (input_location,
+		     "ipa reference summary is missing in ltrans unit");
     }
 }
 
diff --git a/gcc/java/ChangeLog b/gcc/java/ChangeLog
index 3b77d48aa06e2f215b320050bebc90674b6b3eb2..0437f731f5b1968719b2b17b14bc55e29e6a8185 100644
--- a/gcc/java/ChangeLog
+++ b/gcc/java/ChangeLog
@@ -1,3 +1,8 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* class.c, expr.c, jcf-parse.c, jvspec.c: All callers of
+	fatal_error changed to pass input_location as first argument.
+
 2015-10-15  Prathamesh Kulkarni  <prathamesh.kulkarni@linaro.org>
 	
 	* builtins.c: Include calls.h dojump.h emit-rtl.h explow.h expmed.h
diff --git a/gcc/java/class.c b/gcc/java/class.c
index a3a834218f063302e4f0fc12b6b66eb4ca6c7ac2..d1adb581524bbf3d06d9fa9c805373d2094a4346 100644
--- a/gcc/java/class.c
+++ b/gcc/java/class.c
@@ -850,7 +850,7 @@ add_method (tree this_class, int access_flags, tree name, tree method_sig)
     = (const unsigned char *) IDENTIFIER_POINTER (method_sig);
 
   if (sig[0] != '(')
-    fatal_error ("bad method signature");
+    fatal_error (input_location, "bad method signature");
 
   function_type = get_type_from_signature (method_sig);
   fndecl = add_method_1 (this_class, access_flags, name, function_type);
diff --git a/gcc/java/expr.c b/gcc/java/expr.c
index 81ae8daf08f8cf1460cc54a88d02921c73777985..9af9e751275d878b7f74a670a4eba1e56723039e 100644
--- a/gcc/java/expr.c
+++ b/gcc/java/expr.c
@@ -2253,7 +2253,7 @@ build_known_method_ref (tree method, tree method_type ATTRIBUTE_UNUSED,
 	  if (method == meth)
 	    break;
 	  if (meth == NULL_TREE)
-	    fatal_error ("method '%s' not found in class",
+	    fatal_error (input_location, "method '%s' not found in class",
 			 IDENTIFIER_POINTER (DECL_NAME (method)));
 	  method_index++;
 	}
@@ -2445,7 +2445,7 @@ expand_invoke (int opcode, int method_ref_index, int nargs ATTRIBUTE_UNUSED)
       load_class (self_type, 1);
       safe_layout_class (self_type);
       if (TREE_CODE (TYPE_SIZE (self_type)) == ERROR_MARK)
-	fatal_error ("failed to find class '%s'", self_name);
+	fatal_error (input_location, "failed to find class '%s'", self_name);
     }
   layout_class_methods (self_type);
 
diff --git a/gcc/java/jcf-parse.c b/gcc/java/jcf-parse.c
index 02e23c40c80de78915446e21ebaa034a9685ca6b..e609331ae6aadb8297439e0a8f1d58b729f7dbb5 100644
--- a/gcc/java/jcf-parse.c
+++ b/gcc/java/jcf-parse.c
@@ -1114,7 +1114,7 @@ get_constant (JCF *jcf, int index)
 	  {
 	    int char_len = UT8_CHAR_LENGTH (*utf8);
 	    if (char_len < 0 || char_len > 3 || char_len > i)
- 	      fatal_error ("bad string constant");
+ 	      fatal_error (input_location, "bad string constant");
 
 	    utf8 += char_len;
 	    i -= char_len;
@@ -1132,7 +1132,7 @@ get_constant (JCF *jcf, int index)
   jcf->cpool.data[index].t = value;
   return value;
  bad:
-  fatal_error ("bad value constant type %d, index %d", 
+  fatal_error (input_location, "bad value constant type %d, index %d", 
 	       JPOOL_TAG (jcf, index), index);
 }
 
@@ -1443,13 +1443,13 @@ jcf_parse (JCF* jcf)
   bitmap_clear (field_offsets);
 
   if (jcf_parse_preamble (jcf) != 0)
-    fatal_error ("not a valid Java .class file");
+    fatal_error (input_location, "not a valid Java .class file");
   code = jcf_parse_constant_pool (jcf);
   if (code != 0)
-    fatal_error ("error while parsing constant pool");
+    fatal_error (input_location, "error while parsing constant pool");
   code = verify_constant_pool (jcf);
   if (code > 0)
-    fatal_error ("error in constant pool entry #%d\n", code);
+    fatal_error (input_location, "error in constant pool entry #%d\n", code);
 
   jcf_parse_class (jcf);
   if (main_class == NULL_TREE)
@@ -1461,7 +1461,8 @@ jcf_parse (JCF* jcf)
   if (CLASS_PARSED_P (current_class))
     {
       /* FIXME - where was first time */
-      fatal_error ("reading class %s for the second time from %s",
+      fatal_error (input_location,
+		   "reading class %s for the second time from %s",
 		   IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (current_class))),
 		   jcf->filename);
     }
@@ -1479,13 +1480,13 @@ jcf_parse (JCF* jcf)
   
   code = jcf_parse_fields (jcf);
   if (code != 0)
-    fatal_error ("error while parsing fields");
+    fatal_error (input_location, "error while parsing fields");
   code = jcf_parse_methods (jcf);
   if (code != 0)
-    fatal_error ("error while parsing methods");
+    fatal_error (input_location, "error while parsing methods");
   code = jcf_parse_final_attributes (jcf);
   if (code != 0)
-    fatal_error ("error while parsing final attributes");
+    fatal_error (input_location, "error while parsing final attributes");
 
   if (TYPE_REFLECTION_DATA (current_class))
     annotation_write_byte (JV_DONE_ATTR);
@@ -1769,7 +1770,8 @@ java_parse_file (void)
       int avail = 2000;
       finput = fopen (main_input_filename, "r");
       if (finput == NULL)
-	fatal_error ("can%'t open %s: %m", LOCATION_FILE (input_location));
+	fatal_error (input_location,
+		     "can%'t open %s: %m", LOCATION_FILE (input_location));
       list = XNEWVEC (char, avail);
       next = list;
       for (;;)
@@ -1788,7 +1790,7 @@ java_parse_file (void)
 	  if (count == 0)
 	    {
 	      if (! feof (finput))
-		fatal_error ("error closing %s: %m",
+		fatal_error (input_location, "error closing %s: %m",
 			     LOCATION_FILE (input_location));
 	      *next = '\0';
 	      break;
@@ -1903,11 +1905,12 @@ java_parse_file (void)
 
       /* Close previous descriptor, if any */
       if (finput && fclose (finput))
-	fatal_error ("can%'t close input file %s: %m", main_input_filename);
+	fatal_error (input_location,
+		     "can%'t close input file %s: %m", main_input_filename);
       
       finput = fopen (filename, "rb");
       if (finput == NULL)
-	fatal_error ("can%'t open %s: %m", filename);
+	fatal_error (input_location, "can%'t open %s: %m", filename);
 
 #ifdef IO_BUFFER_SIZE
       setvbuf (finput, xmalloc (IO_BUFFER_SIZE),
@@ -1946,7 +1949,7 @@ java_parse_file (void)
 	  linemap_add (line_table, LC_ENTER, false, filename, 0);
 	  input_location = linemap_line_start (line_table, 0, 1);
 	  if (open_in_zip (main_jcf, filename, NULL, 0) <  0)
-	    fatal_error ("bad zip/jar file %s", filename);
+	    fatal_error (input_location, "bad zip/jar file %s", filename);
 	  localToFile = SeenZipFiles;
 	  /* Register all the classes defined there.  */
 	  process_zip_dir ((FILE *) main_jcf->read_state);
@@ -2148,7 +2151,8 @@ parse_zip_file_entries (void)
 	    jcf->zipd        = zdir;
 
 	    if (read_zip_member (jcf, zdir, localToFile) < 0)
-	      fatal_error ("error while reading %s from zip file", file_name);
+	      fatal_error (input_location,
+			   "error while reading %s from zip file", file_name);
 
 	    buffer = XNEWVEC (char, zdir->filename_length + 1 +
 			    (jcf->buffer_end - jcf->buffer));
diff --git a/gcc/java/jvspec.c b/gcc/java/jvspec.c
index 7177176e16877db83fb52c1e295331eb5219fc21..d4efb7377a0abdeb25e7d0e204206a487a9bf878 100644
--- a/gcc/java/jvspec.c
+++ b/gcc/java/jvspec.c
@@ -392,16 +392,17 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
     }
 
   if (saw_D && ! main_class_name)
-    fatal_error ("can%'t specify %<-D%> without %<--main%>");
+    fatal_error (input_location, "can%'t specify %<-D%> without %<--main%>");
 
   if (main_class_name && ! verify_class_name (main_class_name))
-    fatal_error ("%qs is not a valid class name", main_class_name);
+    fatal_error (input_location,
+		 "%qs is not a valid class name", main_class_name);
 
   num_args = argc + added;
   if (saw_resource)
     {
       if (! saw_o)
-	fatal_error ("--resource requires -o");
+	fatal_error (input_location, "--resource requires -o");
     }
   if (saw_C)
     {
@@ -415,7 +416,7 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
 	}
       num_args += 2;  /* For -o NONE. */
       if (saw_o)
-	fatal_error ("cannot specify both -C and -o");
+	fatal_error (input_location, "cannot specify both -C and -o");
     }
   if ((saw_o && java_files_count + class_files_count + zip_files_count > 1)
       || (saw_C && java_files_count > 1)
@@ -427,7 +428,7 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
     {
       filelist_filename = make_temp_file ("jx");
       if (filelist_filename == NULL)
-	fatal_error ("cannot create temporary file");
+	fatal_error (input_location, "cannot create temporary file");
       record_temp_file (filelist_filename, ! saw_save_temps, 0);
       filelist_file = fopen (filelist_filename, "w");
       if (filelist_file == NULL)
@@ -449,7 +450,8 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
   if (combine_inputs || indirect_files_count > 0)
     num_args += 1; /* for "-ffilelist-file" */
   if (combine_inputs && indirect_files_count > 0)
-    fatal_error ("using both @FILE with multiple files not implemented");
+    fatal_error (input_location,
+		 "using both @FILE with multiple files not implemented");
 
   /* There's no point adding -shared-libgcc if we don't have a shared
      libgcc.  */
@@ -533,7 +535,8 @@ lang_specific_driver (struct cl_decoded_option **in_decoded_options,
 
 	case OPT_fmain_:
 	  if (! will_link)
-	    fatal_error ("cannot specify %<main%> class when not linking");
+	    fatal_error (input_location,
+			 "cannot specify %<main%> class when not linking");
 	  --j;
 	  continue;
 	}
diff --git a/gcc/lto-cgraph.c b/gcc/lto-cgraph.c
index 403d9595d5a9e8aea0aeb912242c9789237a7720..ab9524b3b73fd4272ee4992e3bd124db337d0dea 100644
--- a/gcc/lto-cgraph.c
+++ b/gcc/lto-cgraph.c
@@ -1805,7 +1805,7 @@ merge_profile_summaries (struct lto_file_decl_data **file_data_vec)
                       node->lto_file_data->profile_info.runs);
 	node->count_materialization_scale = scale;
 	if (scale < 0)
-	  fatal_error ("Profile information in %s corrupted",
+	  fatal_error (input_location, "Profile information in %s corrupted",
 		       file_data->file_name);
 
 	if (scale == REG_BR_PROB_BASE)
@@ -1837,7 +1837,8 @@ input_symtab (void)
       ib = lto_create_simple_input_block (file_data, LTO_section_symtab_nodes,
 					  &data, &len);
       if (!ib) 
-	fatal_error ("cannot find LTO cgraph in %s", file_data->file_name);
+	fatal_error (input_location,
+		     "cannot find LTO cgraph in %s", file_data->file_name);
       input_profile_summary (ib, file_data);
       file_data->symtab_node_encoder = lto_symtab_encoder_new (true);
       nodes = input_cgraph_1 (file_data, ib);
@@ -1847,7 +1848,7 @@ input_symtab (void)
       ib = lto_create_simple_input_block (file_data, LTO_section_refs,
 					  &data, &len);
       if (!ib)
-	fatal_error ("cannot find LTO section refs in %s",
+	fatal_error (input_location, "cannot find LTO section refs in %s",
 		     file_data->file_name);
       input_refs (ib, nodes);
       lto_destroy_simple_input_block (file_data, LTO_section_refs,
@@ -1914,7 +1915,8 @@ input_offload_tables (void)
 	      vec_safe_push (offload_vars, var_decl);
 	    }
 	  else
-	    fatal_error ("invalid offload table in %s", file_data->file_name);
+	    fatal_error (input_location,
+			 "invalid offload table in %s", file_data->file_name);
 
 	  tag = streamer_read_enum (ib, LTO_symtab_tags, LTO_symtab_last_tag);
 	}
diff --git a/gcc/lto-section-in.c b/gcc/lto-section-in.c
index 7bc014d125251a6dc9479ceed85d974d86936b35..20eded67fbac117d54d927256c1634220bf7e810 100644
--- a/gcc/lto-section-in.c
+++ b/gcc/lto-section-in.c
@@ -457,7 +457,7 @@ lto_free_function_in_decl_state_for_node (symtab_node *node)
 void
 lto_section_overrun (struct lto_input_block *ib)
 {
-  fatal_error ("bytecode stream: trying to read %d bytes "
+  fatal_error (input_location, "bytecode stream: trying to read %d bytes "
 	       "after the end of the input buffer", ib->p - ib->len);
 }
 
@@ -467,6 +467,7 @@ void
 lto_value_range_error (const char *purpose, HOST_WIDE_INT val,
 		       HOST_WIDE_INT min, HOST_WIDE_INT max)
 {
-  fatal_error ("%s out of range: Range is %i to %i, value is %i",
+  fatal_error (input_location,
+	       "%s out of range: Range is %i to %i, value is %i",
 	       purpose, (int)min, (int)max, (int)val);
 }
diff --git a/gcc/lto-streamer-in.c b/gcc/lto-streamer-in.c
index fbb272f7bbff748101223adee47419904a331369..e12d00ac8137fe60bf67344ca504a4599d2eeb16 100644
--- a/gcc/lto-streamer-in.c
+++ b/gcc/lto-streamer-in.c
@@ -815,27 +815,31 @@ fixup_call_stmt_edges_1 (struct cgraph_node *node, gimple *stmts,
   for (cedge = node->callees; cedge; cedge = cedge->next_callee)
     {
       if (gimple_stmt_max_uid (fn) < cedge->lto_stmt_uid)
-        fatal_error ("Cgraph edge statement index out of range");
+        fatal_error (input_location,
+		     "Cgraph edge statement index out of range");
       cedge->call_stmt = as_a <gcall *> (stmts[cedge->lto_stmt_uid - 1]);
       if (!cedge->call_stmt)
-        fatal_error ("Cgraph edge statement index not found");
+        fatal_error (input_location,
+		     "Cgraph edge statement index not found");
     }
   for (cedge = node->indirect_calls; cedge; cedge = cedge->next_callee)
     {
       if (gimple_stmt_max_uid (fn) < cedge->lto_stmt_uid)
-        fatal_error ("Cgraph edge statement index out of range");
+        fatal_error (input_location,
+		     "Cgraph edge statement index out of range");
       cedge->call_stmt = as_a <gcall *> (stmts[cedge->lto_stmt_uid - 1]);
       if (!cedge->call_stmt)
-        fatal_error ("Cgraph edge statement index not found");
+        fatal_error (input_location, "Cgraph edge statement index not found");
     }
   for (i = 0; node->iterate_reference (i, ref); i++)
     if (ref->lto_stmt_uid)
       {
 	if (gimple_stmt_max_uid (fn) < ref->lto_stmt_uid)
-	  fatal_error ("Reference statement index out of range");
+	  fatal_error (input_location,
+		       "Reference statement index out of range");
 	ref->stmt = stmts[ref->lto_stmt_uid - 1];
 	if (!ref->stmt)
-	  fatal_error ("Reference statement index not found");
+	  fatal_error (input_location, "Reference statement index not found");
       }
 }
 
diff --git a/gcc/lto-streamer.c b/gcc/lto-streamer.c
index 6b4e0f279ae6be925531d6f38fef4c751dcd5847..836dce98d9f95c2965b0c5ef52d84718d950e512 100644
--- a/gcc/lto-streamer.c
+++ b/gcc/lto-streamer.c
@@ -406,7 +406,8 @@ void
 lto_check_version (int major, int minor)
 {
   if (major != LTO_major_version || minor != LTO_minor_version)
-    fatal_error ("bytecode stream generated with LTO version %d.%d instead "
+    fatal_error (input_location,
+		 "bytecode stream generated with LTO version %d.%d instead "
 	         "of the expected %d.%d",
 		 major, minor,
 		 LTO_major_version, LTO_minor_version);
diff --git a/gcc/lto-wrapper.c b/gcc/lto-wrapper.c
index e9507717d4447c25bd87527c3d588d06475c2ee2..404cb68e0d1f800628ff69b7672385b88450a3d5 100644
--- a/gcc/lto-wrapper.c
+++ b/gcc/lto-wrapper.c
@@ -109,7 +109,7 @@ maybe_unlink (const char *file)
     {
       if (unlink_if_ordinary (file)
 	  && errno != ENOENT)
-	fatal_error ("deleting LTRANS file %s: %m", file);
+	fatal_error (input_location, "deleting LTRANS file %s: %m", file);
     }
   else if (verbose)
     fprintf (stderr, "[Leaving LTRANS %s]\n", file);
@@ -146,7 +146,7 @@ get_options_from_collect_gcc_options (const char *collect_gcc,
 	  do
 	    {
 	      if (argv_storage[j] == '\0')
-		fatal_error ("malformed COLLECT_GCC_OPTIONS");
+		fatal_error (input_location, "malformed COLLECT_GCC_OPTIONS");
 	      else if (strncmp (&argv_storage[j], "'\\''", 4) == 0)
 		{
 		  argv_storage[k++] = '\'';
@@ -294,7 +294,8 @@ merge_and_complain (struct cl_decoded_option **decoded_options,
 	    if ((*decoded_options)[j].opt_index == foption->opt_index)
 	      break;
 	  if (j == *decoded_options_count)
-	    fatal_error ("Option %s not used consistently in all LTO input"
+	    fatal_error (input_location,
+			 "Option %s not used consistently in all LTO input"
 			 " files", foption->orig_option_with_args_text);
 	  break;
 
@@ -305,7 +306,8 @@ merge_and_complain (struct cl_decoded_option **decoded_options,
 	    if (j == *decoded_options_count)
 	      append_option (decoded_options, decoded_options_count, foption);
 	    else if (foption->value != (*decoded_options)[j].value)
-	      fatal_error ("Option %s not used consistently in all LTO input"
+	      fatal_error (input_location,
+			   "Option %s not used consistently in all LTO input"
 			   " files", foption->orig_option_with_args_text);
 	    break;
 
@@ -730,7 +732,8 @@ compile_images_for_offload_targets (unsigned in_argc, char *in_argv[],
 				 compiler_opts, compiler_opt_count,
 				 linker_opts, linker_opt_count);
       if (!offload_names[i])
-	fatal_error ("problem with building target image for %s\n", names[i]);
+	fatal_error (input_location,
+		     "problem with building target image for %s\n", names[i]);
     }
 
  out:
@@ -749,12 +752,12 @@ copy_file (const char *dest, const char *src)
     {
       size_t len = fread (buffer, 1, 512, s);
       if (ferror (s) != 0)
-	fatal_error ("reading input file");
+	fatal_error (input_location, "reading input file");
       if (len > 0)
 	{
 	  fwrite (buffer, 1, len, d);
 	  if (ferror (d) != 0)
-	    fatal_error ("writing output file");
+	    fatal_error (input_location, "writing output file");
 	}
     }
 }
@@ -779,7 +782,8 @@ find_offloadbeginend (void)
 	char *tmp = xstrdup (paths[i]);
 	strcpy (paths[i] + len - strlen ("begin.o"), "end.o");
 	if (access_check (paths[i], R_OK) != 0)
-	  fatal_error ("installation error, can't find crtoffloadend.o");
+	  fatal_error (input_location,
+		       "installation error, can't find crtoffloadend.o");
 	/* The linker will delete the filenames we give it, so make
 	   copies.  */
 	offloadbegin = make_temp_file (".o");
@@ -790,7 +794,8 @@ find_offloadbeginend (void)
 	break;
       }
   if (i == n_paths)
-    fatal_error ("installation error, can't find crtoffloadbegin.o");
+    fatal_error (input_location,
+		 "installation error, can't find crtoffloadbegin.o");
 
   free_array_of_ptrs ((void **) paths, n_paths);
 }
@@ -893,10 +898,12 @@ run_gcc (unsigned argc, char *argv[])
   /* Get the driver and options.  */
   collect_gcc = getenv ("COLLECT_GCC");
   if (!collect_gcc)
-    fatal_error ("environment variable COLLECT_GCC must be set");
+    fatal_error (input_location,
+		 "environment variable COLLECT_GCC must be set");
   collect_gcc_options = getenv ("COLLECT_GCC_OPTIONS");
   if (!collect_gcc_options)
-    fatal_error ("environment variable COLLECT_GCC_OPTIONS must be set");
+    fatal_error (input_location,
+		 "environment variable COLLECT_GCC_OPTIONS must be set");
   get_options_from_collect_gcc_options (collect_gcc, collect_gcc_options,
 					CL_LANG_ALL,
 					&decoded_options,
@@ -1162,7 +1169,7 @@ run_gcc (unsigned argc, char *argv[])
       struct obstack env_obstack;
 
       if (!stream)
-	fatal_error ("fopen: %s: %m", ltrans_output_file);
+	fatal_error (input_location, "fopen: %s: %m", ltrans_output_file);
 
       /* Parse the list of LTRANS inputs from the WPA stage.  */
       obstack_init (&env_obstack);
@@ -1344,7 +1351,7 @@ main (int argc, char *argv[])
   diagnostic_initialize (global_dc, 0);
 
   if (atexit (lto_wrapper_cleanup) != 0)
-    fatal_error ("atexit failed");
+    fatal_error (input_location, "atexit failed");
 
   if (signal (SIGINT, SIG_IGN) != SIG_IGN)
     signal (SIGINT, fatal_signal);
diff --git a/gcc/lto/ChangeLog b/gcc/lto/ChangeLog
index 98f256a035c0af31717bafda73a365db75e0126b..c77e6ccae40ecd5b2a161ecff0db95cb13385945 100644
--- a/gcc/lto/ChangeLog
+++ b/gcc/lto/ChangeLog
@@ -1,3 +1,8 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* lto-object.c, lto-symtab.c, lto.c: All callers of fatal_error
+	changed to pass input_location as first argument.
+
 2014-12-11  Jan Hubicka  <hubicka@ucw.cz>
 
 	* lto-symtab.c (lto_varpool_replace_node): Merge TLS models.
diff --git a/gcc/lto/lto-object.c b/gcc/lto/lto-object.c
index 08f351c1b4daae94e524225bf3b34714f5d02b7f..34dafb10dd28044eccc5367605e4a6abd52ddd8f 100644
--- a/gcc/lto/lto-object.c
+++ b/gcc/lto/lto-object.c
@@ -208,9 +208,9 @@ lto_obj_file_close (lto_file *file)
       if (errmsg != NULL)
 	{
 	  if (err == 0)
-	    fatal_error ("%s", errmsg);
+	    fatal_error (input_location, "%s", errmsg);
 	  else
-	    fatal_error ("%s: %s", errmsg, xstrerror (err));
+	    fatal_error (input_location, "%s: %s", errmsg, xstrerror (err));
 	}
 
       simple_object_release_write (lo->sobj_w);
@@ -219,7 +219,7 @@ lto_obj_file_close (lto_file *file)
   if (lo->fd != -1)
     {
       if (close (lo->fd) < 0)
-	fatal_error ("close: %s", xstrerror (errno));
+	fatal_error (input_location, "close: %s", xstrerror (errno));
     }
 }
 
@@ -362,9 +362,9 @@ lto_obj_begin_section (const char *name)
   if (lo->section == NULL)
     {
       if (err == 0)
-	fatal_error ("%s", errmsg);
+	fatal_error (input_location, "%s", errmsg);
       else
-	fatal_error ("%s: %s", errmsg, xstrerror (errno));
+	fatal_error (input_location, "%s: %s", errmsg, xstrerror (errno));
     }
 }
 
@@ -386,9 +386,9 @@ lto_obj_append_data (const void *data, size_t len, void *)
   if (errmsg != NULL)
     {
       if (err == 0)
-	fatal_error ("%s", errmsg);
+	fatal_error (input_location, "%s", errmsg);
       else
-	fatal_error ("%s: %s", errmsg, xstrerror (errno));
+	fatal_error (input_location, "%s: %s", errmsg, xstrerror (errno));
     }
 }
 
diff --git a/gcc/lto/lto-symtab.c b/gcc/lto/lto-symtab.c
index 98edb883440a94047c48f8322ed0da5aad018aec..39c9257edc08379d76cd55d37ac20b3d76650be9 100644
--- a/gcc/lto/lto-symtab.c
+++ b/gcc/lto/lto-symtab.c
@@ -382,7 +382,7 @@ lto_symtab_resolve_symbols (symtab_node *first)
 	    && (e->resolution == LDPR_PREVAILING_DEF_IRONLY
 		|| e->resolution == LDPR_PREVAILING_DEF_IRONLY_EXP
 		|| e->resolution == LDPR_PREVAILING_DEF))
-	  fatal_error ("multiple prevailing defs for %qE",
+	  fatal_error (input_location, "multiple prevailing defs for %qE",
 		       DECL_NAME (prevailing->decl));
       return prevailing;
     }
diff --git a/gcc/lto/lto.c b/gcc/lto/lto.c
index a875edeef9ad41caf25ada90ac29f7fa0a9a1e6c..c86f8358f3592e88bcf19d763e4a9b28360b9252 100644
--- a/gcc/lto/lto.c
+++ b/gcc/lto/lto.c
@@ -2328,7 +2328,7 @@ lto_read_section_data (struct lto_file_decl_data *file_data,
       fd = open (file_data->file_name, O_RDONLY|O_BINARY);
       if (fd == -1)
         {
-	  fatal_error ("Cannot open %s", file_data->file_name);
+	  fatal_error (input_location, "Cannot open %s", file_data->file_name);
 	  return NULL;
         }
       fd_name = xstrdup (file_data->file_name);
@@ -2349,7 +2349,7 @@ lto_read_section_data (struct lto_file_decl_data *file_data,
 			  fd, computed_offset);
   if (result == MAP_FAILED)
     {
-      fatal_error ("Cannot map %s", file_data->file_name);
+      fatal_error (input_location, "Cannot map %s", file_data->file_name);
       return NULL;
     }
 
@@ -2360,7 +2360,7 @@ lto_read_section_data (struct lto_file_decl_data *file_data,
       || read (fd, result, len) != (ssize_t) len)
     {
       free (result);
-      fatal_error ("Cannot read %s", file_data->file_name);
+      fatal_error (input_location, "Cannot read %s", file_data->file_name);
       result = NULL;
     }
 #ifdef __MINGW32__
@@ -2474,7 +2474,7 @@ do_stream_out (char *temp_filename, lto_symtab_encoder_t encoder)
 {
   lto_file *file = lto_obj_file_open (temp_filename, true);
   if (!file)
-    fatal_error ("lto_obj_file_open() failed");
+    fatal_error (input_location, "lto_obj_file_open() failed");
   lto_set_current_out_file (file);
 
   ipa_write_optimization_summaries (encoder);
@@ -2497,12 +2497,13 @@ wait_for_child ()
 #endif
       int w = waitpid (0, &status, WUNTRACED | WCONTINUED);
       if (w == -1)
-	fatal_error ("waitpid failed");
+	fatal_error (input_location, "waitpid failed");
 
       if (WIFEXITED (status) && WEXITSTATUS (status))
-	fatal_error ("streaming subprocess failed");
+	fatal_error (input_location, "streaming subprocess failed");
       else if (WIFSIGNALED (status))
-	fatal_error ("streaming subprocess was killed by signal");
+	fatal_error (input_location,
+		     "streaming subprocess was killed by signal");
     }
   while (!WIFEXITED (status) && !WIFSIGNALED (status));
 }
@@ -2578,7 +2579,7 @@ lto_wpa_write_files (void)
 
   /* Open the LTRANS output list.  */
   if (!ltrans_output_list)
-    fatal_error ("no LTRANS output list filename provided");
+    fatal_error (input_location, "no LTRANS output list filename provided");
 
   timevar_push (TV_WHOPR_WPA);
 
@@ -2665,13 +2666,14 @@ lto_wpa_write_files (void)
     }
   ltrans_output_list_stream = fopen (ltrans_output_list, "w");
   if (ltrans_output_list_stream == NULL)
-    fatal_error ("opening LTRANS output list %s: %m", ltrans_output_list);
+    fatal_error (input_location,
+		 "opening LTRANS output list %s: %m", ltrans_output_list);
   for (i = 0; i < n_sets; i++)
     {
       unsigned int len = strlen (temp_filenames[i]);
       if (fwrite (temp_filenames[i], 1, len, ltrans_output_list_stream) < len
 	  || fwrite ("\n", 1, 1, ltrans_output_list_stream) < 1)
-	fatal_error ("writing to LTRANS output list %s: %m",
+	fatal_error (input_location, "writing to LTRANS output list %s: %m",
 		     ltrans_output_list);
      free (temp_filenames[i]);
     }
@@ -2681,7 +2683,8 @@ lto_wpa_write_files (void)
 
   /* Close the LTRANS output list.  */
   if (fclose (ltrans_output_list_stream))
-    fatal_error ("closing LTRANS output list %s: %m", ltrans_output_list);
+    fatal_error (input_location,
+		 "closing LTRANS output list %s: %m", ltrans_output_list);
 
   free_ltrans_partitions();
   free (temp_filename);
@@ -2927,7 +2930,8 @@ read_cgraph_and_symbols (unsigned nfiles, const char **fnames)
 
       resolution = fopen (resolution_file_name, "r");
       if (resolution == NULL)
-	fatal_error ("could not open symbol resolution file: %m");
+	fatal_error (input_location,
+		     "could not open symbol resolution file: %m");
 
       t = fscanf (resolution, "%u", &num_objects);
       gcc_assert (t == 1);
@@ -3067,7 +3071,8 @@ read_cgraph_and_symbols (unsigned nfiles, const char **fnames)
       /* If there were errors during symbol merging bail out, we have no
 	 good way to recover here.  */
       if (seen_error ())
-	fatal_error ("errors during merging of translation units");
+	fatal_error (input_location,
+		     "errors during merging of translation units");
 
       /* Fixup all decls.  */
       lto_fixup_decls (all_file_decl_data);
diff --git a/gcc/objc/objc-act.c b/gcc/objc/objc-act.c
index 610e770e8895281637b54c19ecf640597a2adbab..6bd4dcc29e125321a65e626ba8bf59229bdbcb38 100644
--- a/gcc/objc/objc-act.c
+++ b/gcc/objc/objc-act.c
@@ -485,7 +485,7 @@ objc_write_global_declarations (void)
 	  char * const dumpname = concat (dump_base_name, ".decl", NULL);
 	  gen_declaration_file = fopen (dumpname, "w");
 	  if (gen_declaration_file == 0)
-	    fatal_error ("can%'t open %s: %m", dumpname);
+	    fatal_error (input_location, "can%'t open %s: %m", dumpname);
 	  free (dumpname);
 	}
 
@@ -2038,7 +2038,8 @@ objc_add_method_declaration (bool is_class_method, tree decl, tree attributes)
 	 impossible to get here.  But it's good to have the check in
 	 case the parser changes.
       */
-      fatal_error ("method declaration not in @interface context");
+      fatal_error (input_location,
+		   "method declaration not in @interface context");
     }
 
   if (flag_objc1_only && attributes)
@@ -2863,7 +2864,7 @@ check_protocol_recursively (tree proto, tree list)
 			      /* definition_required */ false);
 
       if (pp == proto)
-	fatal_error ("protocol %qE has circular dependency",
+	fatal_error (input_location, "protocol %qE has circular dependency",
 		     PROTOCOL_NAME (pp));
       if (pp)
 	check_protocol_recursively (proto, PROTOCOL_LIST (pp));
diff --git a/gcc/opts.c b/gcc/opts.c
index 305e349497201526b4a0231abd114ff77972fba7..84627c4e379107444a35af2287785f3986aaf427 100644
--- a/gcc/opts.c
+++ b/gcc/opts.c
@@ -2264,10 +2264,11 @@ setup_core_dumping (diagnostic_context *dc)
   {
     struct rlimit rlim;
     if (getrlimit (RLIMIT_CORE, &rlim) != 0)
-      fatal_error ("getting core file size maximum limit: %m");
+      fatal_error (input_location, "getting core file size maximum limit: %m");
     rlim.rlim_cur = rlim.rlim_max;
     if (setrlimit (RLIMIT_CORE, &rlim) != 0)
-      fatal_error ("setting core file size limit to maximum: %m");
+      fatal_error (input_location,
+		   "setting core file size limit to maximum: %m");
   }
 #endif
   diagnostic_abort_on_error (dc);
diff --git a/gcc/passes.c b/gcc/passes.c
index 411e3bb4d6a0413ad77de139eab9c472072bcb0b..dff70e5bbe9cf74d4eba5e12d22a95634d415ee8 100644
--- a/gcc/passes.c
+++ b/gcc/passes.c
@@ -1455,14 +1455,15 @@ pass_manager::register_pass (struct register_pass_info *pass_info)
      passes should never fail these checks, so we mention plugin in
      the messages.  */
   if (!pass_info->pass)
-      fatal_error ("plugin cannot register a missing pass");
+      fatal_error (input_location, "plugin cannot register a missing pass");
 
   if (!pass_info->pass->name)
-      fatal_error ("plugin cannot register an unnamed pass");
+      fatal_error (input_location, "plugin cannot register an unnamed pass");
 
   if (!pass_info->reference_pass_name)
       fatal_error
-	("plugin cannot register pass %qs without reference pass name",
+	(input_location,
+	 "plugin cannot register pass %qs without reference pass name",
 	 pass_info->pass->name);
 
   /* Try to insert the new pass to the pass lists.  We need to check
@@ -1480,7 +1481,8 @@ pass_manager::register_pass (struct register_pass_info *pass_info)
     success |= position_pass (pass_info, &all_passes);
   if (!success)
     fatal_error
-      ("pass %qs not found but is referenced by new pass %qs",
+      (input_location,
+       "pass %qs not found but is referenced by new pass %qs",
        pass_info->reference_pass_name, pass_info->pass->name);
 
   /* OK, we have successfully inserted the new pass. We need to register
diff --git a/gcc/plugin.c b/gcc/plugin.c
index 7e07b634d2f05af7ff426ec47cd7ec1e2ab03e0c..d924438c9404912d4124325220b287416050c8b5 100644
--- a/gcc/plugin.c
+++ b/gcc/plugin.c
@@ -187,7 +187,8 @@ add_new_plugin (const char* plugin_name)
 			    plugin_name, ".so", NULL);
       if (access (plugin_name, R_OK))
 	fatal_error
-	  ("inaccessible plugin file %s expanded from short plugin name %s: %m",
+	  (input_location,
+	   "inaccessible plugin file %s expanded from short plugin name %s: %m",
 	   plugin_name, base_name);
     }
   else
@@ -595,7 +596,8 @@ try_init_one_plugin (struct plugin_name_args *plugin)
 
   /* Check the plugin license.  */
   if (dlsym (dl_handle, str_license) == NULL)
-    fatal_error ("plugin %s is not licensed under a GPL-compatible license\n"
+    fatal_error (input_location,
+		 "plugin %s is not licensed under a GPL-compatible license\n"
 		 "%s", plugin->full_name, dlerror ());
 
   PTR_UNION_AS_VOID_PTR (plugin_init_union) =
@@ -893,6 +895,7 @@ const char*
 default_plugin_dir_name (void)
 {
   if (!plugindir_string)
-    fatal_error ("-iplugindir <dir> option not passed from the gcc driver");
+    fatal_error (input_location,
+		 "-iplugindir <dir> option not passed from the gcc driver");
   return plugindir_string;
 }
diff --git a/gcc/tlink.c b/gcc/tlink.c
index f96b519ae00b48b2292b6b136fc52ebe4e2acf0a..ec2f9f42c9de3668c9b35f61e2ba95f483b865fd 100644
--- a/gcc/tlink.c
+++ b/gcc/tlink.c
@@ -486,9 +486,9 @@ recompile_files (void)
 	 the new file name already exists.  Therefore, we explicitly
 	 remove the old file first.  */
       if (remove (f->key) == -1)
-	fatal_error ("removing .rpo file: %m");
+	fatal_error (input_location, "removing .rpo file: %m");
       if (rename (outname, f->key) == -1)
-	fatal_error ("renaming .rpo file: %m");
+	fatal_error (input_location, "renaming .rpo file: %m");
 
       if (!f->args)
 	{
diff --git a/gcc/toplev.c b/gcc/toplev.c
index bc2ca3b3a27e0172ee1f3fede9f21aa528762743..c4bc74b6e79753df0c4e01dd5b260d2afc32907f 100644
--- a/gcc/toplev.c
+++ b/gcc/toplev.c
@@ -986,8 +986,8 @@ init_asm_output (const char *name)
 	       || !strcmp (asm_file_name, HOST_BIT_BUCKET))
 	asm_out_file = fopen (asm_file_name, "w");
       else
-	/* Use fatal_error (UNKOWN_LOCATION) instead of just fatal_error to
-	   prevent gcc from printing the first line in the current file. */
+	/* Use UNKOWN_LOCATION to prevent gcc from printing the first
+	   line in the current file. */
 	fatal_error (UNKNOWN_LOCATION,
 		     "input file %qs is the same as output file",
 		     asm_file_name);
@@ -1155,7 +1155,7 @@ open_auxiliary_file (const char *ext)
   filename = concat (aux_base_name, ".", ext, NULL);
   file = fopen (filename, "w");
   if (!file)
-    fatal_error ("can%'t open %s for writing: %m", filename);
+    fatal_error (input_location, "can%'t open %s for writing: %m", filename);
   free (filename);
   return file;
 }
@@ -1576,7 +1576,7 @@ process_options (void)
     {
       aux_info_file = fopen (aux_info_file_name, "w");
       if (aux_info_file == 0)
-	fatal_error ("can%'t open %s: %m", aux_info_file_name);
+	fatal_error (input_location, "can%'t open %s: %m", aux_info_file_name);
     }
 
   if (!targetm_common.have_named_sections)
@@ -1970,9 +1970,9 @@ finalize (bool no_backend)
   if (asm_out_file)
     {
       if (ferror (asm_out_file) != 0)
-	fatal_error ("error writing to %s: %m", asm_file_name);
+	fatal_error (input_location, "error writing to %s: %m", asm_file_name);
       if (fclose (asm_out_file) != 0)
-	fatal_error ("error closing %s: %m", asm_file_name);
+	fatal_error (input_location, "error closing %s: %m", asm_file_name);
     }
 
   if (stack_usage_file)
diff --git a/gcc/tree-streamer-in.c b/gcc/tree-streamer-in.c
index 67d33ed1fbce75d6ecb8d368f3743ea22563c8e5..96f4adacedeb0decd426272771a17d15ec8eafc9 100644
--- a/gcc/tree-streamer-in.c
+++ b/gcc/tree-streamer-in.c
@@ -347,12 +347,14 @@ unpack_ts_function_decl_value_fields (struct bitpack_d *bp, tree expr)
 	                                                                    12);
       if (DECL_BUILT_IN_CLASS (expr) == BUILT_IN_NORMAL
 	  && DECL_FUNCTION_CODE (expr) >= END_BUILTINS)
-	fatal_error ("machine independent builtin code out of range");
+	fatal_error (input_location,
+		     "machine independent builtin code out of range");
       else if (DECL_BUILT_IN_CLASS (expr) == BUILT_IN_MD)
 	{
           tree result = targetm.builtin_decl (DECL_FUNCTION_CODE (expr), true);
 	  if (!result || result == error_mark_node)
-	    fatal_error ("target specific builtin not available");
+	    fatal_error (input_location,
+			 "target specific builtin not available");
 	}
     }
 }
@@ -1138,7 +1140,8 @@ streamer_get_builtin_tree (struct lto_input_block *ib, struct data_in *data_in)
   if (fclass == BUILT_IN_NORMAL)
     {
       if (fcode >= END_BUILTINS)
-	fatal_error ("machine independent builtin code out of range");
+	fatal_error (input_location,
+		     "machine independent builtin code out of range");
       result = builtin_decl_explicit (fcode);
       if (!result
 	  && fcode > BEGIN_CHKP_BUILTINS
@@ -1154,7 +1157,7 @@ streamer_get_builtin_tree (struct lto_input_block *ib, struct data_in *data_in)
     {
       result = targetm.builtin_decl (fcode, true);
       if (!result || result == error_mark_node)
-	fatal_error ("target specific builtin not available");
+	fatal_error (input_location, "target specific builtin not available");
     }
   else
     gcc_unreachable ();
diff --git a/gcc/varpool.c b/gcc/varpool.c
index bd9de6b39b6ecfecbc59f3124025d121034857bc..3bd6eb41b7a679ecf4e793b383039a3bd659e91d 100644
--- a/gcc/varpool.c
+++ b/gcc/varpool.c
@@ -316,7 +316,7 @@ varpool_node::get_constructor (void)
   data = lto_get_section_data (file_data, LTO_section_function_body,
 			       name, &len);
   if (!data)
-    fatal_error ("%s: section %s is missing",
+    fatal_error (input_location, "%s: section %s is missing",
 		 file_data->file_name,
 		 name);
 
diff --git a/libcc1/ChangeLog b/libcc1/ChangeLog
index b0507eb2a9b773e9e916cc306ceec5864e504864..09e75a7138007d689d0f47632d1b9c3128b53ccd 100644
--- a/libcc1/ChangeLog
+++ b/libcc1/ChangeLog
@@ -1,3 +1,8 @@
+2015-01-30  Joseph Myers  <joseph@codesourcery.com>
+
+	* plugin.cc: All callers of fatal_error changed to pass
+	input_location as first argument.
+
 2015-01-09  Michael Collison  <michael.collison@linaro.org>
 
 	* plugin.cc: Include hash-set.h, machmode.h, vec.h, double-int.h,
diff --git a/libcc1/plugin.cc b/libcc1/plugin.cc
index 7e011999aa5e825e2e72ecbb35c3524277866e1d..c4caf05907b57ff4fb33d952d9af0225a3b526a8 100644
--- a/libcc1/plugin.cc
+++ b/libcc1/plugin.cc
@@ -836,13 +836,15 @@ plugin_init (struct plugin_name_args *plugin_info,
 	  errno = 0;
 	  fd = strtol (plugin_info->argv[i].value, &tail, 0);
 	  if (*tail != '\0' || errno != 0)
-	    fatal_error ("%s: invalid file descriptor argument to plugin",
+	    fatal_error (input_location,
+			 "%s: invalid file descriptor argument to plugin",
 			 plugin_info->base_name);
 	  break;
 	}
     }
   if (fd == -1)
-    fatal_error ("%s: required plugin argument %<fd%> is missing",
+    fatal_error (input_location,
+		 "%s: required plugin argument %<fd%> is missing",
 		 plugin_info->base_name);
 
   current_context = new plugin_context (fd);
@@ -851,9 +853,11 @@ plugin_init (struct plugin_name_args *plugin_info,
   cc1_plugin::protocol_int version;
   if (!current_context->require ('H')
       || ! ::cc1_plugin::unmarshall (current_context, &version))
-    fatal_error ("%s: handshake failed", plugin_info->base_name);
+    fatal_error (input_location,
+		 "%s: handshake failed", plugin_info->base_name);
   if (version != GCC_C_FE_VERSION_0)
-    fatal_error ("%s: unknown version in handshake", plugin_info->base_name);
+    fatal_error (input_location,
+		 "%s: unknown version in handshake", plugin_info->base_name);
 
   register_callback (plugin_info->base_name, PLUGIN_PRAGMAS,
 		     plugin_init_extra_pragmas, NULL);