diff --git a/libcc1/Makefile.am b/libcc1/Makefile.am
index f148fdd7aa285fe0c7b950c91c12bdccd4505fd4..3f20513d11b75d60959728491d550a29bba1d7ce 100644
--- a/libcc1/Makefile.am
+++ b/libcc1/Makefile.am
@@ -75,7 +75,7 @@ libcp1plugin_la_LINK = $(LIBTOOL) --tag=CXX $(AM_LIBTOOLFLAGS) \
 LTLDFLAGS = $(shell $(SHELL) $(top_srcdir)/../libtool-ldflags $(LDFLAGS))
 libcc1_la_LDFLAGS = -module -export-symbols $(srcdir)/libcc1.sym
 libcc1_la_SOURCES = findcomp.cc libcc1.cc libcp1.cc \
-		names.cc names.hh $(shared_source) \
+		compiler.cc compiler.hh names.cc names.hh $(shared_source) \
 		$(marshall_c_source) $(marshall_cxx_source)
 libcc1_la_LIBADD = $(libiberty)
 libcc1_la_DEPENDENCIES = $(libiberty_dep)
diff --git a/libcc1/Makefile.in b/libcc1/Makefile.in
index 753d435c9cbe728e7383ca19fae51d1728996f77..d76893e3a24ee9d00a7c4898a801573aceeb4823 100644
--- a/libcc1/Makefile.in
+++ b/libcc1/Makefile.in
@@ -144,8 +144,8 @@ am__installdirs = "$(DESTDIR)$(cc1libdir)" "$(DESTDIR)$(plugindir)"
 LTLIBRARIES = $(cc1lib_LTLIBRARIES) $(plugin_LTLIBRARIES)
 am__objects_1 = callbacks.lo connection.lo marshall.lo
 am__objects_2 =
-am_libcc1_la_OBJECTS = findcomp.lo libcc1.lo libcp1.lo names.lo \
-	$(am__objects_1) $(am__objects_2) $(am__objects_2)
+am_libcc1_la_OBJECTS = findcomp.lo libcc1.lo libcp1.lo compiler.lo \
+	names.lo $(am__objects_1) $(am__objects_2) $(am__objects_2)
 libcc1_la_OBJECTS = $(am_libcc1_la_OBJECTS)
 @ENABLE_PLUGIN_TRUE@am_libcc1_la_rpath = -rpath $(cc1libdir)
 am_libcc1plugin_la_OBJECTS = libcc1plugin.lo $(am__objects_1) \
@@ -428,7 +428,7 @@ libcp1plugin_la_LINK = $(LIBTOOL) --tag=CXX $(AM_LIBTOOLFLAGS) \
 LTLDFLAGS = $(shell $(SHELL) $(top_srcdir)/../libtool-ldflags $(LDFLAGS))
 libcc1_la_LDFLAGS = -module -export-symbols $(srcdir)/libcc1.sym
 libcc1_la_SOURCES = findcomp.cc libcc1.cc libcp1.cc \
-		names.cc names.hh $(shared_source) \
+		compiler.cc compiler.hh names.cc names.hh $(shared_source) \
 		$(marshall_c_source) $(marshall_cxx_source)
 
 libcc1_la_LIBADD = $(libiberty)
@@ -577,6 +577,7 @@ distclean-compile:
 	-rm -f *.tab.c
 
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/callbacks.Plo@am__quote@
+@AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/compiler.Plo@am__quote@
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/connection.Plo@am__quote@
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/findcomp.Plo@am__quote@
 @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libcc1.Plo@am__quote@
diff --git a/libcc1/compiler.cc b/libcc1/compiler.cc
new file mode 100644
index 0000000000000000000000000000000000000000..fede8496862509d18e7dde36294ab54209d76a88
--- /dev/null
+++ b/libcc1/compiler.cc
@@ -0,0 +1,118 @@
+/* Compiler handling for plugin
+   Copyright (C) 2014-2021 Free Software Foundation, Inc.
+
+This file is part of GCC.
+
+GCC is free software; you can redistribute it and/or modify it under
+the terms of the GNU General Public License as published by the Free
+Software Foundation; either version 3, or (at your option) any later
+version.
+
+GCC is distributed in the hope that it will be useful, but WITHOUT ANY
+WARRANTY; without even the implied warranty of MERCHANTABILITY or
+FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+for more details.
+
+You should have received a copy of the GNU General Public License
+along with GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+#include <cc1plugin-config.h>
+#include <string>
+#include <sstream>
+#include "libiberty.h"
+#include "compiler.hh"
+#include "xregex.h"
+#include "findcomp.hh"
+#include "intl.h"
+
+// Construct an appropriate regexp to match the compiler name.
+static std::string
+make_regexp (const char *triplet_regexp, const char *compiler)
+{
+  std::stringstream buf;
+
+  buf << "^" << triplet_regexp << "-";
+
+  // Quote the compiler name in case it has something funny in it.
+  for (const char *p = compiler; *p; ++p)
+    {
+      switch (*p)
+	{
+	case '.':
+	case '^':
+	case '$':
+	case '*':
+	case '+':
+	case '?':
+	case '(':
+	case ')':
+	case '[':
+	case '{':
+	case '\\':
+	case '|':
+	  buf << '\\';
+	  break;
+	}
+      buf << *p;
+    }
+  buf << "$";
+
+  return buf.str ();
+}
+
+char *
+cc1_plugin::compiler::find (const char *, std::string &) const
+{
+  return xstrdup (_("Compiler has not been specified"));
+}
+
+char *
+cc1_plugin::compiler_triplet_regexp::find (const char *base,
+					   std::string &compiler) const
+{
+  std::string rx = make_regexp (triplet_regexp_.c_str (), base);
+  if (verbose)
+    fprintf (stderr, _("searching for compiler matching regex %s\n"),
+	     rx.c_str());
+  regex_t triplet;
+  int code = regcomp (&triplet, rx.c_str (), REG_EXTENDED | REG_NOSUB);
+  if (code != 0)
+    {
+      size_t len = regerror (code, &triplet, NULL, 0);
+      char err[len];
+
+      regerror (code, &triplet, err, len);
+
+      return concat ("Could not compile regexp \"",
+		     rx.c_str (),
+		     "\": ",
+		     err,
+		     (char *) NULL);
+    }
+
+  if (!find_compiler (triplet, &compiler))
+    {
+      regfree (&triplet);
+      return concat ("Could not find a compiler matching \"",
+		     rx.c_str (),
+		     "\"",
+		     (char *) NULL);
+    }
+  regfree (&triplet);
+  if (verbose)
+    fprintf (stderr, _("found compiler %s\n"), compiler.c_str());
+  return NULL;
+}
+
+char *
+cc1_plugin::compiler_driver_filename::find (const char *,
+					    std::string &compiler) const
+{
+  // Simulate fnotice by fprintf.
+  if (verbose)
+    fprintf (stderr, _("using explicit compiler filename %s\n"),
+	     driver_filename_.c_str());
+  compiler = driver_filename_;
+  return NULL;
+}
diff --git a/libcc1/compiler.hh b/libcc1/compiler.hh
new file mode 100644
index 0000000000000000000000000000000000000000..638f7c09f634f146a9ddf53fe871da9cf4117d1b
--- /dev/null
+++ b/libcc1/compiler.hh
@@ -0,0 +1,83 @@
+/* Compiler handling for plugin
+   Copyright (C) 2014-2020 Free Software Foundation, Inc.
+
+This file is part of GCC.
+
+GCC is free software; you can redistribute it and/or modify it under
+the terms of the GNU General Public License as published by the Free
+Software Foundation; either version 3, or (at your option) any later
+version.
+
+GCC is distributed in the hope that it will be useful, but WITHOUT ANY
+WARRANTY; without even the implied warranty of MERCHANTABILITY or
+FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
+for more details.
+
+You should have received a copy of the GNU General Public License
+along with GCC; see the file COPYING3.  If not see
+<http://www.gnu.org/licenses/>.  */
+
+#ifndef CC1_PLUGIN_COMPILER_HH
+#define CC1_PLUGIN_COMPILER_HH
+
+namespace cc1_plugin
+{
+
+  // Base class for compiler.
+  class compiler
+  {
+  public:
+    explicit compiler (bool v)
+      : verbose (v)
+    {
+    }
+
+    virtual ~compiler () = default;
+
+    // Find the compiler.  BASE is the base name of the compiler, see
+    // compiler-name.hh.  This sets COMPILER to the resulting path.
+    // Returns nullptr on success, or a malloc'd error string on
+    // failure.
+    virtual char *find (const char *base, std::string &compiler) const;
+
+    void set_verbose (bool v)
+    {
+      verbose = v;
+    }
+
+  protected:
+    bool verbose;
+  };
+
+  /* Compiler to set by set_triplet_regexp.  */
+  class compiler_triplet_regexp : public compiler
+  {
+  private:
+    std::string triplet_regexp_;
+  public:
+
+    char *find (const char *base, std::string &compiler) const override;
+
+    compiler_triplet_regexp (bool v, std::string triplet_regexp)
+      : compiler (v), triplet_regexp_ (triplet_regexp)
+    {
+    }
+  };
+
+  /* Compiler to set by set_driver_filename.  */
+  class compiler_driver_filename : public compiler
+  {
+  private:
+    std::string driver_filename_;
+  public:
+    char *find (const char *base, std::string &compiler) const override;
+
+    compiler_driver_filename (bool v, std::string driver_filename)
+      : compiler (v), driver_filename_ (driver_filename)
+    {
+    }
+  };
+
+}
+
+#endif // CC1_PLUGIN_COMPILER_HH
diff --git a/libcc1/libcc1.cc b/libcc1/libcc1.cc
index e00355955b6ea2ca02359b8bc21c20c6cf5b6e12..ea52c26d78322f9202d970a90f1dfaa0094c245e 100644
--- a/libcc1/libcc1.cc
+++ b/libcc1/libcc1.cc
@@ -28,18 +28,15 @@ along with GCC; see the file COPYING3.  If not see
 #include <errno.h>
 #include <sys/stat.h>
 #include <stdlib.h>
-#include <sstream>
 #include "marshall.hh"
 #include "rpc.hh"
 #include "connection.hh"
 #include "names.hh"
 #include "callbacks.hh"
 #include "libiberty.h"
-#include "xregex.h"
-#include "findcomp.hh"
 #include "compiler-name.hh"
-#include "intl.h"
 #include "gcc-c-interface.h"
+#include "compiler.hh"
 
 struct libcc1;
 
@@ -71,54 +68,7 @@ struct libcc1 : public gcc_c_context
   /* Non-zero as an equivalent to gcc driver option "-v".  */
   bool verbose;
 
-  /* Compiler to set by set_triplet_regexp or set_driver_filename.  */
-  class compiler
-  {
-  protected:
-    libcc1 *self_;
-  public:
-    compiler (libcc1 *self) : self_ (self)
-    {
-    }
-    virtual char *find (std::string &compiler) const;
-    virtual ~compiler ()
-    {
-    }
-  };
-
-  std::unique_ptr<compiler> compilerp;
-
-  /* Compiler to set by set_triplet_regexp.  */
-  class compiler_triplet_regexp : public compiler
-  {
-  private:
-    std::string triplet_regexp_;
-  public:
-    char *find (std::string &compiler) const override;
-    compiler_triplet_regexp (libcc1 *self, std::string triplet_regexp)
-      : compiler (self), triplet_regexp_ (triplet_regexp)
-    {
-    }
-    virtual ~compiler_triplet_regexp ()
-    {
-    }
-  };
-
-  /* Compiler to set by set_driver_filename.  */
-  class compiler_driver_filename : public compiler
-  {
-  private:
-    std::string driver_filename_;
-  public:
-    char *find (std::string &compiler) const override;
-    compiler_driver_filename (libcc1 *self, std::string driver_filename)
-      : compiler (self), driver_filename_ (driver_filename)
-    {
-    }
-    virtual ~compiler_driver_filename ()
-    {
-    }
-  };
+  std::unique_ptr<cc1_plugin::compiler> compilerp;
 };
 
 // A local subclass of connection that holds a back-pointer to the
@@ -151,7 +101,7 @@ libcc1::libcc1 (const gcc_base_vtable *v,
     args (),
     source_file (),
     verbose (false),
-    compilerp (new libcc1::compiler (this))
+    compilerp (new cc1_plugin::compiler (verbose))
 {
   base.ops = v;
   c_ops = cv;
@@ -252,101 +202,14 @@ static const struct gcc_c_fe_vtable c_vtable =
 
 
 
-// Construct an appropriate regexp to match the compiler name.
-static std::string
-make_regexp (const char *triplet_regexp, const char *compiler)
-{
-  std::stringstream buf;
-
-  buf << "^" << triplet_regexp << "-";
-
-  // Quote the compiler name in case it has something funny in it.
-  for (const char *p = compiler; *p; ++p)
-    {
-      switch (*p)
-	{
-	case '.':
-	case '^':
-	case '$':
-	case '*':
-	case '+':
-	case '?':
-	case '(':
-	case ')':
-	case '[':
-	case '{':
-	case '\\':
-	case '|':
-	  buf << '\\';
-	  break;
-	}
-      buf << *p;
-    }
-  buf << "$";
-
-  return buf.str ();
-}
-
 static void
 libcc1_set_verbose (struct gcc_base_context *s, int /* bool */ verbose)
 {
   libcc1 *self = (libcc1 *) s;
 
   self->verbose = verbose != 0;
-}
-
-char *
-libcc1::compiler::find (std::string &compiler ATTRIBUTE_UNUSED) const
-{
-  return xstrdup (_("Compiler has not been specified"));
-}
-
-char *
-libcc1::compiler_triplet_regexp::find (std::string &compiler) const
-{
-  std::string rx = make_regexp (triplet_regexp_.c_str (), C_COMPILER_NAME);
-  if (self_->verbose)
-    fprintf (stderr, _("searching for compiler matching regex %s\n"),
-	     rx.c_str());
-  regex_t triplet;
-  int code = regcomp (&triplet, rx.c_str (), REG_EXTENDED | REG_NOSUB);
-  if (code != 0)
-    {
-      size_t len = regerror (code, &triplet, NULL, 0);
-      char err[len];
-
-      regerror (code, &triplet, err, len);
-
-      return concat ("Could not compile regexp \"",
-		     rx.c_str (),
-		     "\": ",
-		     err,
-		     (char *) NULL);
-    }
-
-  if (!find_compiler (triplet, &compiler))
-    {
-      regfree (&triplet);
-      return concat ("Could not find a compiler matching \"",
-		     rx.c_str (),
-		     "\"",
-		     (char *) NULL);
-    }
-  regfree (&triplet);
-  if (self_->verbose)
-    fprintf (stderr, _("found compiler %s\n"), compiler.c_str());
-  return NULL;
-}
-
-char *
-libcc1::compiler_driver_filename::find (std::string &compiler) const
-{
-  // Simulate fnotice by fprintf.
-  if (self_->verbose)
-    fprintf (stderr, _("using explicit compiler filename %s\n"),
-	     driver_filename_.c_str());
-  compiler = driver_filename_;
-  return NULL;
+  if (self->compilerp != nullptr)
+    self->compilerp->set_verbose (self->verbose);
 }
 
 static char *
@@ -356,7 +219,7 @@ libcc1_set_arguments (struct gcc_base_context *s,
   libcc1 *self = (libcc1 *) s;
 
   std::string compiler;
-  char *errmsg = self->compilerp->find (compiler);
+  char *errmsg = self->compilerp->find (C_COMPILER_NAME, compiler);
   if (errmsg != NULL)
     return errmsg;
 
@@ -374,8 +237,9 @@ libcc1_set_triplet_regexp (struct gcc_base_context *s,
 {
   libcc1 *self = (libcc1 *) s;
 
-  self->compilerp.reset (new libcc1::compiler_triplet_regexp (self,
-							      triplet_regexp));
+  self->compilerp.reset
+    (new cc1_plugin::compiler_triplet_regexp (self->verbose,
+					      triplet_regexp));
   return NULL;
 }
 
@@ -385,8 +249,9 @@ libcc1_set_driver_filename (struct gcc_base_context *s,
 {
   libcc1 *self = (libcc1 *) s;
 
-  self->compilerp.reset (new libcc1::compiler_driver_filename (self,
-							       driver_filename));
+  self->compilerp.reset
+    (new cc1_plugin::compiler_driver_filename (self->verbose,
+					       driver_filename));
   return NULL;
 }
 
diff --git a/libcc1/libcp1.cc b/libcc1/libcp1.cc
index 4bd8c6b00b657de45d4bb25551c3e19ee24e7e02..c57ac8c66a6b736ec1ac62f7f076179a18130c55 100644
--- a/libcc1/libcp1.cc
+++ b/libcc1/libcp1.cc
@@ -28,17 +28,14 @@ along with GCC; see the file COPYING3.  If not see
 #include <errno.h>
 #include <sys/stat.h>
 #include <stdlib.h>
-#include <sstream>
 #include "marshall-cp.hh"
 #include "rpc.hh"
 #include "connection.hh"
 #include "names.hh"
 #include "callbacks.hh"
 #include "libiberty.h"
-#include "xregex.h"
-#include "findcomp.hh"
 #include "compiler-name.hh"
-#include "intl.h"
+#include "compiler.hh"
 
 struct libcp1;
 
@@ -72,54 +69,7 @@ struct libcp1 : public gcc_cp_context
   /* Non-zero as an equivalent to gcc driver option "-v".  */
   bool verbose;
 
-  /* Compiler to set by set_triplet_regexp or set_driver_filename.  */
-  class compiler
-  {
-  protected:
-    libcp1 *self_;
-  public:
-    compiler (libcp1 *self) : self_ (self)
-    {
-    }
-    virtual char *find (std::string &compiler) const;
-    virtual ~compiler ()
-    {
-    }
-  };
-
-  std::unique_ptr<compiler> compilerp;
-
-  /* Compiler to set by set_triplet_regexp.  */
-  class compiler_triplet_regexp : public compiler
-  {
-  private:
-    std::string triplet_regexp_;
-  public:
-    char *find (std::string &compiler) const override;
-    compiler_triplet_regexp (libcp1 *self, std::string triplet_regexp)
-      : compiler (self), triplet_regexp_ (triplet_regexp)
-    {
-    }
-    virtual ~compiler_triplet_regexp ()
-    {
-    }
-  };
-
-  /* Compiler to set by set_driver_filename.  */
-  class compiler_driver_filename : public compiler
-  {
-  private:
-    std::string driver_filename_;
-  public:
-    char *find (std::string &compiler) const override;
-    compiler_driver_filename (libcp1 *self, std::string driver_filename)
-      : compiler (self), driver_filename_ (driver_filename)
-    {
-    }
-    virtual ~compiler_driver_filename ()
-    {
-    }
-  };
+  std::unique_ptr<cc1_plugin::compiler> compilerp;
 };
 
 // A local subclass of connection that holds a back-pointer to the
@@ -152,7 +102,7 @@ libcp1::libcp1 (const gcc_base_vtable *v,
     args (),
     source_file (),
     verbose (false),
-    compilerp (new libcp1::compiler (this))
+    compilerp (new cc1_plugin::compiler (verbose))
 {
   base.ops = v;
   cp_ops = cv;
@@ -275,101 +225,14 @@ static const struct gcc_cp_fe_vtable cp_vtable =
 
 
 
-// Construct an appropriate regexp to match the compiler name.
-static std::string
-make_regexp (const char *triplet_regexp, const char *compiler)
-{
-  std::stringstream buf;
-
-  buf << "^" << triplet_regexp << "-";
-
-  // Quote the compiler name in case it has something funny in it.
-  for (const char *p = compiler; *p; ++p)
-    {
-      switch (*p)
-	{
-	case '.':
-	case '^':
-	case '$':
-	case '*':
-	case '+':
-	case '?':
-	case '(':
-	case ')':
-	case '[':
-	case '{':
-	case '\\':
-	case '|':
-	  buf << '\\';
-	  break;
-	}
-      buf << *p;
-    }
-  buf << "$";
-
-  return buf.str ();
-}
-
 static void
 libcp1_set_verbose (struct gcc_base_context *s, int /* bool */ verbose)
 {
   libcp1 *self = (libcp1 *) s;
 
   self->verbose = verbose != 0;
-}
-
-char *
-libcp1::compiler::find (std::string &compiler ATTRIBUTE_UNUSED) const
-{
-  return xstrdup (_("Compiler has not been specified"));
-}
-
-char *
-libcp1::compiler_triplet_regexp::find (std::string &compiler) const
-{
-  std::string rx = make_regexp (triplet_regexp_.c_str (), CP_COMPILER_NAME);
-  if (self_->verbose)
-    fprintf (stderr, _("searching for compiler matching regex %s\n"),
-	     rx.c_str());
-  regex_t triplet;
-  int code = regcomp (&triplet, rx.c_str (), REG_EXTENDED | REG_NOSUB);
-  if (code != 0)
-    {
-      size_t len = regerror (code, &triplet, NULL, 0);
-      char err[len];
-
-      regerror (code, &triplet, err, len);
-
-      return concat ("Could not compile regexp \"",
-		     rx.c_str (),
-		     "\": ",
-		     err,
-		     (char *) NULL);
-    }
-
-  if (!find_compiler (triplet, &compiler))
-    {
-      regfree (&triplet);
-      return concat ("Could not find a compiler matching \"",
-		     rx.c_str (),
-		     "\"",
-		     (char *) NULL);
-    }
-  regfree (&triplet);
-  if (self_->verbose)
-    fprintf (stderr, _("found compiler %s\n"), compiler.c_str());
-  return NULL;
-}
-
-char *
-libcp1::compiler_driver_filename::find (std::string &compiler) const
-{
-  // Simulate fnotice by fprintf.
-  if (self_->verbose)
-    fprintf (stderr, _("using explicit compiler filename %s\n"),
-	     driver_filename_.c_str());
-  compiler = driver_filename_;
-  return NULL;
+  if (self->compilerp != nullptr)
+    self->compilerp->set_verbose (self->verbose);
 }
 
 static char *
@@ -379,7 +242,7 @@ libcp1_set_arguments (struct gcc_base_context *s,
   libcp1 *self = (libcp1 *) s;
 
   std::string compiler;
-  char *errmsg = self->compilerp->find (compiler);
+  char *errmsg = self->compilerp->find (CP_COMPILER_NAME, compiler);
   if (errmsg != NULL)
     return errmsg;
 
@@ -397,8 +260,9 @@ libcp1_set_triplet_regexp (struct gcc_base_context *s,
 {
   libcp1 *self = (libcp1 *) s;
 
-  self->compilerp.reset (new libcp1::compiler_triplet_regexp (self,
-							      triplet_regexp));
+  self->compilerp.reset
+    (new cc1_plugin::compiler_triplet_regexp (self->verbose,
+					      triplet_regexp));
   return NULL;
 }
 
@@ -408,8 +272,9 @@ libcp1_set_driver_filename (struct gcc_base_context *s,
 {
   libcp1 *self = (libcp1 *) s;
 
-  self->compilerp.reset (new libcp1::compiler_driver_filename (self,
-							       driver_filename));
+  self->compilerp.reset
+    (new cc1_plugin::compiler_driver_filename (self->verbose,
+					       driver_filename));
   return NULL;
 }