[Git][ghc/ghc][wip/kirchner/ast] AST: move Data instance definition for ModuleName to GHC.Unit.Types

Fabian Kirchner (@kirchner) gitlab at gitlab.haskell.org
Sat Jun 8 14:28:15 UTC 2024



Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC


Commits:
af609165 by Fabian Kirchner at 2024-06-08T16:28:04+02:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

- - - - -


2 changed files:

- compiler/GHC/Unit/Types.hs
- compiler/Language/Haskell/Syntax/Module/Name.hs


Changes:

=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -735,3 +735,9 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
+
+instance Data ModuleName where
+  -- don't traverse?
+  toConstr _   = abstractConstr "ModuleName"
+  gunfold _ _  = error "gunfold"
+  dataTypeOf _ = mkNoRepType "ModuleName"


=====================================
compiler/Language/Haskell/Syntax/Module/Name.hs
=====================================
@@ -2,13 +2,11 @@ module Language.Haskell.Syntax.Module.Name where
 
 import Prelude
 
-import Data.Data
 import Data.Char (isAlphaNum)
 import Control.DeepSeq
 import qualified Text.ParserCombinators.ReadP as Parse
 import System.FilePath
 
-import GHC.Utils.Misc (abstractConstr)
 import GHC.Data.FastString
 
 -- | A ModuleName is essentially a simple string, e.g. @Data.List at .
@@ -17,12 +15,6 @@ newtype ModuleName = ModuleName FastString deriving (Show, Eq)
 instance Ord ModuleName where
   nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2
 
-instance Data ModuleName where
-  -- don't traverse?
-  toConstr _   = abstractConstr "ModuleName"
-  gunfold _ _  = error "gunfold"
-  dataTypeOf _ = mkNoRepType "ModuleName"
-
 instance NFData ModuleName where
   rnf x = x `seq` ()
 



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/af609165552ef09dbab96e39436863af524e4218
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/20240608/93dc7e8d/attachment-0001.html>


More information about the ghc-commits mailing list