diff --git a/gcc/common.opt b/gcc/common.opt
index 50bcc523fd2b2aa7e267985d3cce9040dadf74a3..e558385c7f46275501cec739bb4c9d90b28e8084 100644
--- a/gcc/common.opt
+++ b/gcc/common.opt
@@ -1208,6 +1208,10 @@ fchecking=
 Common Joined RejectNegative UInteger Var(flag_checking)
 Perform internal consistency checkings.
 
+fcanon-prefix-map
+Common Var(common_deferred_options) Defer
+For -f*-prefix-map= options compare canonicalized pathnames rather than just strings.
+
 fcode-hoisting
 Common Var(flag_code_hoisting) Optimization
 Enable code hoisting.
diff --git a/gcc/doc/cppopts.texi b/gcc/doc/cppopts.texi
index 872629eeb4db519dde03e706b5667a68ce6a8d2e..ce225541abe0d2b503fb549b2df06d41640732b5 100644
--- a/gcc/doc/cppopts.texi
+++ b/gcc/doc/cppopts.texi
@@ -305,7 +305,7 @@ to change an absolute path to a relative path by using @file{.} for
 @var{new} which can result in more reproducible builds that are
 location independent.  This option also affects
 @code{__builtin_FILE()} during compilation.  See also
-@option{-ffile-prefix-map}.
+@option{-ffile-prefix-map} and @option{-fcanon-prefix-map}.
 
 @opindex fexec-charset
 @cindex character set, execution
diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi
index beb606fcd1bdf744acc8c71ea957467302958827..3a6a97862b0e42b039134cf9a80fc72247f442cd 100644
--- a/gcc/doc/invoke.texi
+++ b/gcc/doc/invoke.texi
@@ -191,7 +191,7 @@ in the following sections.
 -dumpdir @var{dumppfx}  -x @var{language}  @gol
 -v  -###  --help@r{[}=@var{class}@r{[},@dots{}@r{]]}  --target-help  --version @gol
 -pass-exit-codes  -pipe  -specs=@var{file}  -wrapper  @gol
-@@@var{file}  -ffile-prefix-map=@var{old}=@var{new}  @gol
+@@@var{file}  -ffile-prefix-map=@var{old}=@var{new}  -fcanon-prefix-map  @gol
 -fplugin=@var{file}  -fplugin-arg-@var{name}=@var{arg}  @gol
 -fdump-ada-spec@r{[}-slim@r{]}  -fada-spec-parent=@var{unit}  -fdump-go-spec=@var{file}}
 
@@ -2207,9 +2207,20 @@ files resided in directory @file{@var{new}} instead.  Specifying this
 option is equivalent to specifying all the individual
 @option{-f*-prefix-map} options.  This can be used to make reproducible
 builds that are location independent.  Directories referenced by
-directives are not affected by these options. See also
-@option{-fmacro-prefix-map}, @option{-fdebug-prefix-map} and
-@option{-fprofile-prefix-map}.
+directives are not affected by these options.  See also
+@option{-fmacro-prefix-map}, @option{-fdebug-prefix-map},
+@option{-fprofile-prefix-map} and @option{-fcanon-prefix-map}.
+
+@item -fcanon-prefix-map
+@opindex fcanon-prefix-map
+For the @option{-f*-prefix-map} options normally comparison
+of @file{@var{old}} prefix against the filename that would be normally
+referenced in the result of the compilation is done using textual
+comparison of the prefixes, or ignoring character case for case insensitive
+filesystems and considering slashes and backslashes as equal on DOS based
+filesystems.  The @option{-fcanon-prefix-map} causes such comparisons
+to be done on canonicalized paths of @file{@var{old}}
+and the referenced filename.
 
 @opindex fplugin
 @item -fplugin=@var{name}.so
@@ -11362,7 +11373,8 @@ build-time path with an install-time path in the debug info.  It can
 also be used to change an absolute path to a relative path by using
 @file{.} for @var{new}.  This can give more reproducible builds, which
 are location independent, but may require an extra command to tell GDB
-where to find the source files. See also @option{-ffile-prefix-map}.
+where to find the source files. See also @option{-ffile-prefix-map}
+and @option{-fcanon-prefix-map}.
 
 @opindex fvar-tracking
 @item -fvar-tracking
@@ -16550,7 +16562,7 @@ When compiling files residing in directory @file{@var{old}}, record
 profiling information (with @option{--coverage})
 describing them as if the files resided in
 directory @file{@var{new}} instead.
-See also @option{-ffile-prefix-map}.
+See also @option{-ffile-prefix-map} and @option{-fcanon-prefix-map}.
 
 @opindex fprofile-update
 @item -fprofile-update=@var{method}
diff --git a/gcc/file-prefix-map.cc b/gcc/file-prefix-map.cc
index 795756ccc881b478a8d133b8c4d861bdca21f0b4..0e6db7c142ac7b2b225276d177927e396d65862f 100644
--- a/gcc/file-prefix-map.cc
+++ b/gcc/file-prefix-map.cc
@@ -30,6 +30,7 @@ struct file_prefix_map
   const char *new_prefix;
   size_t old_len;
   size_t new_len;
+  bool canonicalize;
   struct file_prefix_map *next;
 };
 
@@ -51,8 +52,16 @@ add_prefix_map (file_prefix_map *&maps, const char *arg, const char *opt)
       return;
     }
   map = XNEW (file_prefix_map);
+  map->canonicalize = flag_canon_prefix_map;
   map->old_prefix = xstrndup (arg, p - arg);
   map->old_len = p - arg;
+  if (map->canonicalize)
+    {
+      char *realname = lrealpath (map->old_prefix);
+      free (const_cast <char *> (map->old_prefix));
+      map->old_prefix = realname;
+      map->old_len = strlen (realname);
+    }
   p++;
   map->new_prefix = xstrdup (p);
   map->new_len = strlen (p);
@@ -70,34 +79,49 @@ remap_filename (file_prefix_map *maps, const char *filename)
   file_prefix_map *map;
   char *s;
   const char *name;
-  char *realname;
+  const char *realname = NULL;
   size_t name_len;
 
-  if (!filename || lbasename (filename) == filename)
+  if (!filename)
     return filename;
 
-  realname = lrealpath (filename);
-
   for (map = maps; map; map = map->next)
-    if (filename_ncmp (realname, map->old_prefix, map->old_len) == 0)
+    if (map->canonicalize)
+      {
+	if (realname == NULL)
+	  {
+	    if (lbasename (filename) == filename)
+	      realname = filename;
+	    else
+	      realname = lrealpath (filename);
+	  }
+	if (filename_ncmp (realname, map->old_prefix, map->old_len) == 0)
+	  break;
+      }
+    else if (filename_ncmp (filename, map->old_prefix, map->old_len) == 0)
       break;
   if (!map)
     {
-      free (realname);
+      if (realname != filename)
+	free (const_cast <char *> (realname));
       return filename;
     }
-  name = realname + map->old_len;
+  if (map->canonicalize)
+    name = realname + map->old_len;
+  else
+    name = filename + map->old_len;
   name_len = strlen (name) + 1;
 
   s = (char *) ggc_alloc_atomic (name_len + map->new_len);
   memcpy (s, map->new_prefix, map->new_len);
   memcpy (s + map->new_len, name, name_len);
-  free (realname);
+  if (realname != filename)
+    free (const_cast <char *> (realname));
   return s;
 }
 
 /* NOTE: if adding another -f*-prefix-map option then don't forget to
-   ignore it in DW_AT_producer (dwarf2out.cc).  */
+   ignore it in DW_AT_producer (gen_command_line_string in opts.cc).  */
 
 /* Linked lists of file_prefix_map structures.  */
 static file_prefix_map *macro_prefix_maps; /* -fmacro-prefix-map  */
diff --git a/gcc/file-prefix-map.h b/gcc/file-prefix-map.h
index 73b48abe2e27c90c85b8ce9ee5bd499ffd75b0ca..23dce0cabd379dd3852a5cd197517e59f66376b2 100644
--- a/gcc/file-prefix-map.h
+++ b/gcc/file-prefix-map.h
@@ -22,6 +22,7 @@ void add_macro_prefix_map (const char *);
 void add_debug_prefix_map (const char *);
 void add_file_prefix_map (const char *);
 void add_profile_prefix_map (const char *);
+extern bool flag_canon_prefix_map;
 
 const char *remap_macro_filename (const char *);
 const char *remap_debug_filename (const char *);
diff --git a/gcc/lto-opts.cc b/gcc/lto-opts.cc
index 896ff4d5c6866e3dd88f95891fb5630ff28b98f3..c9bee9d4197348c3b20d574cb9d786889595699f 100644
--- a/gcc/lto-opts.cc
+++ b/gcc/lto-opts.cc
@@ -150,6 +150,7 @@ lto_write_options (void)
 	case OPT_ffile_prefix_map_:
 	case OPT_fmacro_prefix_map_:
 	case OPT_fprofile_prefix_map_:
+	case OPT_fcanon_prefix_map:
 	case OPT_fwhole_program:
 	  continue;
 
diff --git a/gcc/opts-global.cc b/gcc/opts-global.cc
index b7bba23a3235f7d04b88d88b674bacd23c12940d..054169158b13ca144e4f06412968246cdf37a470 100644
--- a/gcc/opts-global.cc
+++ b/gcc/opts-global.cc
@@ -367,6 +367,7 @@ handle_common_deferred_options (void)
   if (flag_opt_info)
     opt_info_switch_p (NULL);
 
+  flag_canon_prefix_map = false;
   FOR_EACH_VEC_ELT (v, i, opt)
     {
       switch (opt->opt_index)
@@ -395,6 +396,10 @@ handle_common_deferred_options (void)
 	  add_profile_prefix_map (opt->arg);
 	  break;
 
+	case OPT_fcanon_prefix_map:
+	  flag_canon_prefix_map = opt->value;
+	  break;
+
 	case OPT_fdump_:
 	  g->get_dumps ()->dump_switch_p (opt->arg);
 	  break;
diff --git a/gcc/opts.cc b/gcc/opts.cc
index a032cd4ce5821bac5b4f10d5ec961d8c4b4c4d2a..3bc17a187fe18295875e72c8ce921227ccf72cd1 100644
--- a/gcc/opts.cc
+++ b/gcc/opts.cc
@@ -34,10 +34,14 @@ along with GCC; see the file COPYING3.  If not see
 #include "diagnostic-color.h"
 #include "version.h"
 #include "selftest.h"
+#include "file-prefix-map.h"
 
 /* In this file all option sets are explicit.  */
 #undef OPTION_SET_P
 
+/* Set by -fcanon-prefix-map.  */
+bool flag_canon_prefix_map;
+
 static void set_Wstrict_aliasing (struct gcc_options *opts, int onoff);
 
 /* Names of fundamental debug info formats indexed by enum
@@ -2819,6 +2823,10 @@ common_handle_option (struct gcc_options *opts,
       /* Deferred.  */
       break;
 
+    case OPT_fcanon_prefix_map:
+      flag_canon_prefix_map = value;
+      break;
+
     case OPT_fcallgraph_info:
       opts->x_flag_callgraph_info = CALLGRAPH_INFO_NAKED;
       break;
@@ -3725,6 +3733,7 @@ gen_command_line_string (cl_decoded_option *options,
       case OPT_fmacro_prefix_map_:
       case OPT_ffile_prefix_map_:
       case OPT_fprofile_prefix_map_:
+      case OPT_fcanon_prefix_map:
       case OPT_fcompare_debug:
       case OPT_fchecking:
       case OPT_fchecking_: