diff --git a/compiler/GHC/Iface/Errors/Ppr.hs b/compiler/GHC/Iface/Errors/Ppr.hs
index 031e4fd75c690061e39c2cb733de66e732ceead0..3b260efcb43f0a4aa0c7a121ea62adea418316d9 100644
--- a/compiler/GHC/Iface/Errors/Ppr.hs
+++ b/compiler/GHC/Iface/Errors/Ppr.hs
@@ -65,6 +65,8 @@ interfaceErrorHints = \ case
     missingInterfaceErrorHints err
   Can'tFindNameInInterface {} ->
     noHints
+  CircularImport {} ->
+    noHints
 
 missingInterfaceErrorHints :: MissingInterfaceError -> [GhcHint]
 missingInterfaceErrorHints = \case
@@ -86,6 +88,8 @@ interfaceErrorReason (Can'tFindInterface err _)
   = missingInterfaceErrorReason err
 interfaceErrorReason (Can'tFindNameInInterface {})
   = ErrorWithoutFlag
+interfaceErrorReason (CircularImport {})
+  = ErrorWithoutFlag
 
 missingInterfaceErrorReason :: MissingInterfaceError -> DiagnosticReason
 missingInterfaceErrorReason = \ case
@@ -287,6 +291,9 @@ interfaceErrorDiagnostic opts = \ case
       LookingForSig sig ->
         hang (text "Could not find interface file for signature" <+> quotes (ppr sig) <> colon)
           2 (missingInterfaceErrorDiagnostic opts err)
+  CircularImport mod ->
+    text "Circular imports: module" <+> quotes (ppr mod)
+    <+> text "depends on itself"
 
 readInterfaceErrorDiagnostic :: ReadInterfaceError -> SDoc
 readInterfaceErrorDiagnostic = \ case
diff --git a/compiler/GHC/Iface/Errors/Types.hs b/compiler/GHC/Iface/Errors/Types.hs
index a421c2eeb7e549f16eff35d467a57a17a977b66b..50ccf6ba32b0cd0606d6fec7591ed3729b2bb335 100644
--- a/compiler/GHC/Iface/Errors/Types.hs
+++ b/compiler/GHC/Iface/Errors/Types.hs
@@ -45,6 +45,7 @@ data IfaceMessage
   | Can'tFindNameInInterface
       Name
       [TyThing] -- possibly relevant TyThings
+  | CircularImport !Module
   deriving Generic
 
 data MissingInterfaceError
diff --git a/compiler/GHC/IfaceToCore.hs b/compiler/GHC/IfaceToCore.hs
index 2a81b9c2a0701b6283c3cdc29a6530d257cc09a6..e37f34ef4608a15f9b0ad568d6b9312ab03fe5e9 100644
--- a/compiler/GHC/IfaceToCore.hs
+++ b/compiler/GHC/IfaceToCore.hs
@@ -605,7 +605,7 @@ tcHiBootIface hsc_src mod
                              (LookingForHiBoot mod)
                 in failWithTc (TcRnInterfaceError diag)
               -- The hi-boot file has mysteriously disappeared.
-              NotBoot -> failWithTc (mkTcRnUnknownMessage $ mkPlainError noHints moduleLoop)
+              NotBoot -> failWithTc (TcRnInterfaceError (CircularImport mod))
               -- Someone below us imported us!
               -- This is a loop with no hi-boot in the way
     }}}}
@@ -613,11 +613,6 @@ tcHiBootIface hsc_src mod
     need = text "Need the hi-boot interface for" <+> ppr mod
                  <+> text "to compare against the Real Thing"
 
-    moduleLoop = text "Circular imports: module" <+> quotes (ppr mod)
-                     <+> text "depends on itself"
-
-
-
 mkSelfBootInfo :: ModIface -> ModDetails -> TcRn SelfBootInfo
 mkSelfBootInfo iface mds
   = do -- NB: This is computed DIRECTLY from the ModIface rather
diff --git a/compiler/GHC/Types/Error/Codes.hs b/compiler/GHC/Types/Error/Codes.hs
index 33cdd696f3312afdd3bea7d517c95a396b138155..5025ff022fae0b4f9c1b884ba1d2af12c304e9d6 100644
--- a/compiler/GHC/Types/Error/Codes.hs
+++ b/compiler/GHC/Types/Error/Codes.hs
@@ -719,6 +719,7 @@ type family GhcDiagnosticCode c = n | n -> c where
   GhcDiagnosticCode "NoUnitIdMatching"                              = 51294
   GhcDiagnosticCode "NotAModule"                                    = 35235
   GhcDiagnosticCode "Can'tFindNameInInterface"                      = 83249
+  GhcDiagnosticCode "CircularImport"                                = 75429
   GhcDiagnosticCode "HiModuleNameMismatchWarn"                      = 53693
   GhcDiagnosticCode "ExceptionOccurred"                             = 47808