[Git][ghc/ghc][master] compiler: Fix orientation of GHC.Hs.Doc boot file

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Oct 11 07:58:14 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
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

- - - - -


4 changed files:

- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Unit/Types.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- − compiler/Language/Haskell/Syntax/ImpExp.hs-boot


Changes:

=====================================
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)
+


=====================================
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


=====================================
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
 
 {-
 ************************************************************************


=====================================
compiler/Language/Haskell/Syntax/ImpExp.hs-boot deleted
=====================================
@@ -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



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8584504b68418eaa12f1332a22ccb7d354aacc00

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8584504b68418eaa12f1332a22ccb7d354aacc00
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241011/4823b9d5/attachment-0001.html>


More information about the ghc-commits mailing list