From 8584504b68418eaa12f1332a22ccb7d354aacc00 Mon Sep 17 00:00:00 2001
From: Matthew Pickering <matthewtpickering@gmail.com>
Date: Thu, 10 Oct 2024 12:02:21 +0100
Subject: [PATCH] compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592
---
 compiler/GHC/Hs/Doc.hs-boot                   | 19 +++++++++++++++++++
 compiler/GHC/Unit/Types.hs                    |  2 +-
 compiler/Language/Haskell/Syntax/ImpExp.hs    |  2 +-
 .../Language/Haskell/Syntax/ImpExp.hs-boot    | 16 ----------------
 4 files changed, 21 insertions(+), 18 deletions(-)
 create mode 100644 compiler/GHC/Hs/Doc.hs-boot
 delete mode 100644 compiler/Language/Haskell/Syntax/ImpExp.hs-boot

diff --git a/compiler/GHC/Hs/Doc.hs-boot b/compiler/GHC/Hs/Doc.hs-boot
new file mode 100644
index 00000000000..160908e84ef
--- /dev/null
+++ b/compiler/GHC/Hs/Doc.hs-boot
@@ -0,0 +1,19 @@
+{-# LANGUAGE RoleAnnotations #-}
+module GHC.Hs.Doc where
+
+-- See #21592 for progress on removing this boot file.
+
+import GHC.Types.SrcLoc
+import GHC.Hs.DocString
+import Data.Kind
+
+type role WithHsDocIdentifiers representational nominal
+type WithHsDocIdentifiers :: Type -> Type -> Type
+data WithHsDocIdentifiers a pass
+
+type HsDoc :: Type -> Type
+type HsDoc = WithHsDocIdentifiers HsDocString
+
+type LHsDoc :: Type -> Type
+type LHsDoc pass = Located (HsDoc pass)
+
diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs
index 02036046ab9..b470790c2c2 100644
--- a/compiler/GHC/Unit/Types.hs
+++ b/compiler/GHC/Unit/Types.hs
@@ -110,7 +110,7 @@ import qualified Data.ByteString as BS
 import qualified Data.ByteString.Char8 as BS.Char8
 
 import Language.Haskell.Syntax.Module.Name
-import {-# SOURCE #-} Language.Haskell.Syntax.ImpExp (IsBootInterface(..))
+import Language.Haskell.Syntax.ImpExp (IsBootInterface(..))
 
 ---------------------------------------------------------------------
 -- MODULES
diff --git a/compiler/Language/Haskell/Syntax/ImpExp.hs b/compiler/Language/Haskell/Syntax/ImpExp.hs
index 47f8be01678..b1fd879f067 100644
--- a/compiler/Language/Haskell/Syntax/ImpExp.hs
+++ b/compiler/Language/Haskell/Syntax/ImpExp.hs
@@ -16,7 +16,7 @@ import Data.Int (Int)
 
 import Control.DeepSeq
 
-import GHC.Hs.Doc -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
+import {-# SOURCE #-} GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
 
 {-
 ************************************************************************
diff --git a/compiler/Language/Haskell/Syntax/ImpExp.hs-boot b/compiler/Language/Haskell/Syntax/ImpExp.hs-boot
deleted file mode 100644
index 68bd7fdc535..00000000000
--- a/compiler/Language/Haskell/Syntax/ImpExp.hs-boot
+++ /dev/null
@@ -1,16 +0,0 @@
-module Language.Haskell.Syntax.ImpExp where
-
-import Data.Eq
-import Data.Ord
-import Text.Show
-import Data.Data
-
--- This boot file should be short lived: As soon as the dependency on
--- `GHC.Hs.Doc` is gone we'll no longer have cycles and can get rid this file.
-
-data IsBootInterface = NotBoot | IsBoot
-
-instance Eq IsBootInterface
-instance Ord IsBootInterface
-instance Show IsBootInterface
-instance Data IsBootInterface
-- 
GitLab