summaryrefslogtreecommitdiff
path: root/compiler/GHC
diff options
context:
space:
mode:
authorromes <rodrigo.m.mesquita@gmail.com>2022-06-29 15:36:43 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-07-03 14:11:31 -0400
commitc43dbac08b0d56406fe13de1e9b49c944f478b4a (patch)
tree1a0a40e0095544aa814455e1f0b71fe44cf09c42 /compiler/GHC
parentf9f8099598fd169fa2f17305fc660e5c473f8836 (diff)
downloadhaskell-c43dbac08b0d56406fe13de1e9b49c944f478b4a.tar.gz
Refactor ModuleName to L.H.S.Module.Name
ModuleName used to live in GHC.Unit.Module.Name. In this commit, the definition of ModuleName and its associated functions are moved to Language.Haskell.Syntax.Module.Name according to the current plan towards making the AST GHC-independent. The instances for ModuleName for Outputable, Uniquable and Binary were moved to the module in which the class is defined because these instances depend on GHC. The instance of Eq for ModuleName is slightly changed to no longer depend on unique explicitly and instead uses FastString's instance of Eq.
Diffstat (limited to 'compiler/GHC')
-rw-r--r--compiler/GHC/Builtin/Names.hs3
-rw-r--r--compiler/GHC/Builtin/Names/TH.hs3
-rw-r--r--compiler/GHC/ByteCode/Linker.hs3
-rw-r--r--compiler/GHC/Core/DataCon.hs3
-rw-r--r--compiler/GHC/Core/Opt/CallerCC.hs3
-rw-r--r--compiler/GHC/Core/Opt/Simplify.hs2
-rw-r--r--compiler/GHC/Driver/Pipeline.hs-boot3
-rw-r--r--compiler/GHC/Driver/Pipeline/Execute.hs3
-rw-r--r--compiler/GHC/Driver/Pipeline/Phases.hs3
-rw-r--r--compiler/GHC/Hs/Doc.hs5
-rw-r--r--compiler/GHC/Hs/ImpExp.hs6
-rw-r--r--compiler/GHC/Tc/Deriv/Generics.hs4
-rw-r--r--compiler/GHC/Types/Unique.hs6
-rw-r--r--compiler/GHC/Unit/Home.hs3
-rw-r--r--compiler/GHC/Unit/Module.hs5
-rw-r--r--compiler/GHC/Unit/Module/Deps.hs1
-rw-r--r--compiler/GHC/Unit/Module/Env.hs3
-rw-r--r--compiler/GHC/Unit/Module/Name.hs98
-rw-r--r--compiler/GHC/Unit/Parser.hs4
-rw-r--r--compiler/GHC/Unit/Types.hs2
-rw-r--r--compiler/GHC/Unit/Types.hs-boot2
-rw-r--r--compiler/GHC/Utils/Binary.hs6
-rw-r--r--compiler/GHC/Utils/Outputable.hs14
23 files changed, 62 insertions, 123 deletions
diff --git a/compiler/GHC/Builtin/Names.hs b/compiler/GHC/Builtin/Names.hs
index dba466aa8d..115a7f53f4 100644
--- a/compiler/GHC/Builtin/Names.hs
+++ b/compiler/GHC/Builtin/Names.hs
@@ -136,7 +136,6 @@ where
import GHC.Prelude
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import GHC.Types.Name.Occurrence
import GHC.Types.Name.Reader
import GHC.Types.Unique
@@ -145,6 +144,8 @@ import GHC.Types.Name
import GHC.Types.SrcLoc
import GHC.Data.FastString
+import Language.Haskell.Syntax.Module.Name
+
{-
************************************************************************
* *
diff --git a/compiler/GHC/Builtin/Names/TH.hs b/compiler/GHC/Builtin/Names/TH.hs
index 2eb5e13530..3908f5091c 100644
--- a/compiler/GHC/Builtin/Names/TH.hs
+++ b/compiler/GHC/Builtin/Names/TH.hs
@@ -10,7 +10,6 @@ import GHC.Prelude ()
import GHC.Builtin.Names( mk_known_key_name )
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import GHC.Types.Name( Name )
import GHC.Types.Name.Occurrence( tcName, clsName, dataName, varName )
import GHC.Types.Name.Reader( RdrName, nameRdrName )
@@ -18,6 +17,8 @@ import GHC.Types.Unique
import GHC.Builtin.Uniques
import GHC.Data.FastString
+import Language.Haskell.Syntax.Module.Name
+
-- To add a name, do three things
--
-- 1) Allocate a key
diff --git a/compiler/GHC/ByteCode/Linker.hs b/compiler/GHC/ByteCode/Linker.hs
index c9339317d2..c3af3d4e85 100644
--- a/compiler/GHC/ByteCode/Linker.hs
+++ b/compiler/GHC/ByteCode/Linker.hs
@@ -31,7 +31,6 @@ import GHC.Builtin.PrimOps
import GHC.Builtin.Names
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import GHC.Data.FastString
import GHC.Data.SizedSeq
@@ -43,6 +42,8 @@ import GHC.Utils.Outputable
import GHC.Types.Name
import GHC.Types.Name.Env
+import Language.Haskell.Syntax.Module.Name
+
-- Standard libraries
import Data.Array.Unboxed
import Foreign.Ptr
diff --git a/compiler/GHC/Core/DataCon.hs b/compiler/GHC/Core/DataCon.hs
index 01ab6414c3..0d436a93f0 100644
--- a/compiler/GHC/Core/DataCon.hs
+++ b/compiler/GHC/Core/DataCon.hs
@@ -86,7 +86,6 @@ import GHC.Types.Var.Env
import GHC.Types.Basic
import GHC.Data.FastString
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import GHC.Utils.Binary
import GHC.Types.Unique.FM ( UniqFM )
import GHC.Types.Unique.Set
@@ -105,6 +104,8 @@ import qualified Data.Data as Data
import Data.Char
import Data.List( find )
+import Language.Haskell.Syntax.Module.Name
+
{-
Data constructor representation
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Core/Opt/CallerCC.hs b/compiler/GHC/Core/Opt/CallerCC.hs
index ba9f809092..1bdb4d7afc 100644
--- a/compiler/GHC/Core/Opt/CallerCC.hs
+++ b/compiler/GHC/Core/Opt/CallerCC.hs
@@ -31,7 +31,6 @@ import GHC.Types.CostCentre
import GHC.Types.CostCentre.State
import GHC.Types.Name hiding (varName)
import GHC.Types.Tickish
-import GHC.Unit.Module.Name
import GHC.Unit.Module.ModGuts
import GHC.Types.SrcLoc
import GHC.Types.Var
@@ -43,6 +42,8 @@ import GHC.Utils.Panic
import qualified GHC.Utils.Binary as B
import Data.Char
+import Language.Haskell.Syntax.Module.Name
+
addCallerCostCentres :: ModGuts -> CoreM ModGuts
addCallerCostCentres guts = do
dflags <- getDynFlags
diff --git a/compiler/GHC/Core/Opt/Simplify.hs b/compiler/GHC/Core/Opt/Simplify.hs
index de049523cc..d26fd28de2 100644
--- a/compiler/GHC/Core/Opt/Simplify.hs
+++ b/compiler/GHC/Core/Opt/Simplify.hs
@@ -66,7 +66,7 @@ import GHC.Builtin.Names( runRWKey )
import GHC.Data.Maybe ( isNothing, orElse )
import GHC.Data.FastString
-import GHC.Unit.Module ( moduleName, pprModuleName )
+import GHC.Unit.Module ( moduleName )
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Panic.Plain
diff --git a/compiler/GHC/Driver/Pipeline.hs-boot b/compiler/GHC/Driver/Pipeline.hs-boot
index 3467ff4ced..72ba57a0d1 100644
--- a/compiler/GHC/Driver/Pipeline.hs-boot
+++ b/compiler/GHC/Driver/Pipeline.hs-boot
@@ -5,9 +5,10 @@ import GHC.Driver.Env.Types ( HscEnv )
import GHC.ForeignSrcLang ( ForeignSrcLang )
import GHC.Prelude (FilePath, IO)
import GHC.Unit.Module.Location (ModLocation)
-import GHC.Unit.Module.Name (ModuleName)
import GHC.Driver.Session (DynFlags)
+import Language.Haskell.Syntax.Module.Name
+
-- These are used in GHC.Driver.Pipeline.Execute, but defined in terms of runPipeline
compileForeign :: HscEnv -> ForeignSrcLang -> FilePath -> IO FilePath
compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> ModuleName -> IO ()
diff --git a/compiler/GHC/Driver/Pipeline/Execute.hs b/compiler/GHC/Driver/Pipeline/Execute.hs
index ff62a9a6db..7390735f28 100644
--- a/compiler/GHC/Driver/Pipeline/Execute.hs
+++ b/compiler/GHC/Driver/Pipeline/Execute.hs
@@ -22,7 +22,6 @@ import GHC.Driver.Pipeline.Phases
import GHC.Driver.Env hiding (Hsc)
import GHC.Unit.Module.Location
import GHC.Driver.Phases
-import GHC.Unit.Module.Name ( ModuleName )
import GHC.Unit.Types
import GHC.Types.SourceFile
import GHC.Unit.Module.Status
@@ -83,6 +82,8 @@ import GHC.Driver.Env.KnotVars
import GHC.Driver.Config.Finder
import GHC.Rename.Names
+import Language.Haskell.Syntax.Module.Name
+
newtype HookedUse a = HookedUse { runHookedUse :: (Hooks, PhaseHook) -> IO a }
deriving (Functor, Applicative, Monad, MonadIO, MonadThrow, MonadCatch) via (ReaderT (Hooks, PhaseHook) IO)
diff --git a/compiler/GHC/Driver/Pipeline/Phases.hs b/compiler/GHC/Driver/Pipeline/Phases.hs
index 431c9e0b1d..aa11801b45 100644
--- a/compiler/GHC/Driver/Pipeline/Phases.hs
+++ b/compiler/GHC/Driver/Pipeline/Phases.hs
@@ -16,11 +16,12 @@ import GHC.Types.Error
import GHC.Driver.Errors.Types
import GHC.Fingerprint.Type
import GHC.Unit.Module.Location ( ModLocation )
-import GHC.Unit.Module.Name ( ModuleName )
import GHC.Unit.Module.ModIface
import GHC.Linker.Types
import GHC.Driver.Phases
+import Language.Haskell.Syntax.Module.Name ( ModuleName )
+
-- Typed Pipeline Phases
-- MP: TODO: We need to refine the arguments to each of these phases so recompilation
-- can be smarter. For example, rather than passing a whole HscEnv, just pass the options
diff --git a/compiler/GHC/Hs/Doc.hs b/compiler/GHC/Hs/Doc.hs
index 91f584c8d9..209f9608eb 100644
--- a/compiler/GHC/Hs/Doc.hs
+++ b/compiler/GHC/Hs/Doc.hs
@@ -36,7 +36,6 @@ import qualified GHC.Data.EnumSet as EnumSet
import GHC.Data.EnumSet (EnumSet)
import GHC.Types.Avail
import GHC.Types.Name.Set
-import GHC.Unit.Module.Name
import GHC.Driver.Flags
import Control.Applicative (liftA2)
@@ -48,13 +47,15 @@ import qualified Data.Map as Map
import Data.List.NonEmpty (NonEmpty(..))
import GHC.LanguageExtensions.Type
import qualified GHC.Utils.Outputable as O
-import Language.Haskell.Syntax.Extension
import GHC.Hs.Extension
import GHC.Types.Unique.Map
import Data.List (sortBy)
import GHC.Hs.DocString
+import Language.Haskell.Syntax.Extension
+import Language.Haskell.Syntax.Module.Name
+
-- | A docstring with the (probable) identifiers found in it.
type HsDoc = WithHsDocIdentifiers HsDocString
diff --git a/compiler/GHC/Hs/ImpExp.hs b/compiler/GHC/Hs/ImpExp.hs
index 1f13d8a2fe..06500705ba 100644
--- a/compiler/GHC/Hs/ImpExp.hs
+++ b/compiler/GHC/Hs/ImpExp.hs
@@ -29,8 +29,6 @@ import GHC.Types.FieldLabel ( FieldLabel )
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Types.SrcLoc
-import Language.Haskell.Syntax.Extension
-import Language.Haskell.Syntax.ImpExp
import GHC.Parser.Annotation
import GHC.Hs.Extension
import GHC.Types.Name
@@ -39,6 +37,10 @@ import GHC.Types.PkgQual
import Data.Data
import Data.Maybe
+import Language.Haskell.Syntax.Extension
+import Language.Haskell.Syntax.Module.Name
+import Language.Haskell.Syntax.ImpExp
+
{-
************************************************************************
* *
diff --git a/compiler/GHC/Tc/Deriv/Generics.hs b/compiler/GHC/Tc/Deriv/Generics.hs
index 6240de3205..bae4ca79bf 100644
--- a/compiler/GHC/Tc/Deriv/Generics.hs
+++ b/compiler/GHC/Tc/Deriv/Generics.hs
@@ -33,8 +33,8 @@ import GHC.Core.DataCon
import GHC.Core.TyCon
import GHC.Core.FamInstEnv ( FamInst, FamFlavor(..), mkSingleCoAxiom )
import GHC.Tc.Instance.Family
-import GHC.Unit.Module ( moduleName, moduleNameFS
- , moduleUnit, unitFS, getModule )
+import GHC.Unit.Module ( moduleName, moduleUnit
+ , unitFS, getModule )
import GHC.Iface.Env ( newGlobalBinder )
import GHC.Types.Name hiding ( varName )
import GHC.Types.Name.Reader
diff --git a/compiler/GHC/Types/Unique.hs b/compiler/GHC/Types/Unique.hs
index f4538bf579..60d1c452e2 100644
--- a/compiler/GHC/Types/Unique.hs
+++ b/compiler/GHC/Types/Unique.hs
@@ -59,6 +59,8 @@ import GHC.Exts (indexCharOffAddr#, Char(..), Int(..))
import Data.Char ( chr, ord )
+import Language.Haskell.Syntax.Module.Name
+
{-
************************************************************************
* *
@@ -187,6 +189,10 @@ instance Uniquable FastString where
instance Uniquable Int where
getUnique i = mkUniqueGrimily i
+instance Uniquable ModuleName where
+ getUnique (ModuleName nm) = getUnique nm
+
+
{-
************************************************************************
* *
diff --git a/compiler/GHC/Unit/Home.hs b/compiler/GHC/Unit/Home.hs
index c72d21e537..4f871d10fb 100644
--- a/compiler/GHC/Unit/Home.hs
+++ b/compiler/GHC/Unit/Home.hs
@@ -33,9 +33,10 @@ where
import GHC.Prelude
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import Data.Maybe
+import Language.Haskell.Syntax.Module.Name
+
-- | Information about the home unit (i.e., the until that will contain the
-- modules we are compiling)
--
diff --git a/compiler/GHC/Unit/Module.hs b/compiler/GHC/Unit/Module.hs
index b9813b95f5..7ae0059b71 100644
--- a/compiler/GHC/Unit/Module.hs
+++ b/compiler/GHC/Unit/Module.hs
@@ -18,7 +18,7 @@ module GHC.Unit.Module
( module GHC.Unit.Types
-- * The ModuleName type
- , module GHC.Unit.Module.Name
+ , module Language.Haskell.Syntax.Module.Name
-- * The ModLocation type
, module GHC.Unit.Module.Location
@@ -47,11 +47,12 @@ import GHC.Prelude
import GHC.Types.Unique.DSet
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import GHC.Unit.Module.Location
import GHC.Unit.Module.Env
import GHC.Utils.Misc
+import Language.Haskell.Syntax.Module.Name
+
-- | A 'Module' is definite if it has no free holes.
moduleIsDefinite :: Module -> Bool
moduleIsDefinite = isEmptyUniqDSet . moduleFreeHoles
diff --git a/compiler/GHC/Unit/Module/Deps.hs b/compiler/GHC/Unit/Module/Deps.hs
index 5a50f42b35..9099ee2f0d 100644
--- a/compiler/GHC/Unit/Module/Deps.hs
+++ b/compiler/GHC/Unit/Module/Deps.hs
@@ -24,7 +24,6 @@ import GHC.Prelude
import GHC.Types.SafeHaskell
import GHC.Types.Name
-import GHC.Unit.Module.Name
import GHC.Unit.Module.Imported
import GHC.Unit.Module
import GHC.Unit.Home
diff --git a/compiler/GHC/Unit/Module/Env.hs b/compiler/GHC/Unit/Module/Env.hs
index e8307229f7..32ca0b12cd 100644
--- a/compiler/GHC/Unit/Module/Env.hs
+++ b/compiler/GHC/Unit/Module/Env.hs
@@ -37,7 +37,6 @@ where
import GHC.Prelude
-import GHC.Unit.Module.Name (ModuleName)
import GHC.Types.Unique
import GHC.Types.Unique.FM
import GHC.Types.Unique.DFM
@@ -54,6 +53,8 @@ import qualified Data.Set as Set
import qualified GHC.Data.FiniteMap as Map
import GHC.Utils.Outputable
+import Language.Haskell.Syntax.Module.Name
+
-- | A map keyed off of 'Module's
newtype ModuleEnv elt = ModuleEnv (Map NDModule elt)
diff --git a/compiler/GHC/Unit/Module/Name.hs b/compiler/GHC/Unit/Module/Name.hs
deleted file mode 100644
index b7bf62857c..0000000000
--- a/compiler/GHC/Unit/Module/Name.hs
+++ /dev/null
@@ -1,98 +0,0 @@
-{-# OPTIONS_GHC -Wno-orphans #-} -- Outputable and Module Name
-
--- | The ModuleName type
-module GHC.Unit.Module.Name
- ( ModuleName
- , pprModuleName
- , moduleNameFS
- , moduleNameString
- , moduleNameSlashes, moduleNameColons
- , mkModuleName
- , mkModuleNameFS
- , stableModuleNameCmp
- , parseModuleName
- )
-where
-
-import {-# SOURCE #-} Language.Haskell.Syntax.ImpExp (ModuleName(..))
-
-import GHC.Prelude
-
-import GHC.Utils.Outputable
-import GHC.Types.Unique
-import GHC.Data.FastString
-import GHC.Utils.Binary
-import GHC.Utils.Misc
-
-import Control.DeepSeq
-import Data.Data
-import System.FilePath
-
-import qualified Text.ParserCombinators.ReadP as Parse
-import Text.ParserCombinators.ReadP (ReadP)
-import Data.Char (isAlphaNum)
-
-instance Uniquable ModuleName where
- getUnique (ModuleName nm) = getUnique nm
-
-instance Eq ModuleName where
- nm1 == nm2 = getUnique nm1 == getUnique nm2
-
-instance Ord ModuleName where
- nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2
-
-instance Outputable ModuleName where
- ppr = pprModuleName
-
-instance Binary ModuleName where
- put_ bh (ModuleName fs) = put_ bh fs
- get bh = do fs <- get bh; return (ModuleName fs)
-
-instance Data ModuleName where
- -- don't traverse?
- toConstr _ = abstractConstr "ModuleName"
- gunfold _ _ = error "gunfold"
- dataTypeOf _ = mkNoRepType "ModuleName"
-
-instance NFData ModuleName where
- rnf x = x `seq` ()
-
-stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
--- ^ Compares module names lexically, rather than by their 'Unique's
-stableModuleNameCmp n1 n2 = moduleNameFS n1 `lexicalCompareFS` moduleNameFS n2
-
-pprModuleName :: ModuleName -> SDoc
-pprModuleName (ModuleName nm) =
- getPprStyle $ \ sty ->
- if codeStyle sty
- then ztext (zEncodeFS nm)
- else ftext nm
-
-moduleNameFS :: ModuleName -> FastString
-moduleNameFS (ModuleName mod) = mod
-
-moduleNameString :: ModuleName -> String
-moduleNameString (ModuleName mod) = unpackFS mod
-
-mkModuleName :: String -> ModuleName
-mkModuleName s = ModuleName (mkFastString s)
-
-mkModuleNameFS :: FastString -> ModuleName
-mkModuleNameFS s = ModuleName s
-
--- |Returns the string version of the module name, with dots replaced by slashes.
---
-moduleNameSlashes :: ModuleName -> String
-moduleNameSlashes = dots_to_slashes . moduleNameString
- where dots_to_slashes = map (\c -> if c == '.' then pathSeparator else c)
-
--- |Returns the string version of the module name, with dots replaced by colons.
---
-moduleNameColons :: ModuleName -> String
-moduleNameColons = dots_to_colons . moduleNameString
- where dots_to_colons = map (\c -> if c == '.' then ':' else c)
-
-parseModuleName :: ReadP ModuleName
-parseModuleName = fmap mkModuleName
- $ Parse.munch1 (\c -> isAlphaNum c || c `elem` "_.")
-
diff --git a/compiler/GHC/Unit/Parser.hs b/compiler/GHC/Unit/Parser.hs
index f9735306de..bac6ba4bf1 100644
--- a/compiler/GHC/Unit/Parser.hs
+++ b/compiler/GHC/Unit/Parser.hs
@@ -10,13 +10,14 @@ where
import GHC.Prelude
import GHC.Unit.Types
-import GHC.Unit.Module.Name
import GHC.Data.FastString
import qualified Text.ParserCombinators.ReadP as Parse
import Text.ParserCombinators.ReadP (ReadP, (<++))
import Data.Char (isAlphaNum)
+import Language.Haskell.Syntax.Module.Name (ModuleName, parseModuleName)
+
parseUnit :: ReadP Unit
parseUnit = parseVirtUnitId <++ parseDefUnitId
where
@@ -55,4 +56,3 @@ parseModSubst = Parse.between (Parse.char '[') (Parse.char ']')
v <- parseHoleyModule
return (k, v)
-
diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs
index e99fea94d4..f71ce9c02e 100644
--- a/compiler/GHC/Unit/Types.hs
+++ b/compiler/GHC/Unit/Types.hs
@@ -91,7 +91,6 @@ where
import GHC.Prelude
import GHC.Types.Unique
import GHC.Types.Unique.DSet
-import GHC.Unit.Module.Name
import GHC.Utils.Binary
import GHC.Utils.Outputable
import GHC.Data.FastString
@@ -107,6 +106,7 @@ import Data.Bifunctor
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(..))
---------------------------------------------------------------------
diff --git a/compiler/GHC/Unit/Types.hs-boot b/compiler/GHC/Unit/Types.hs-boot
index 21a0f6bc79..a7e09126d5 100644
--- a/compiler/GHC/Unit/Types.hs-boot
+++ b/compiler/GHC/Unit/Types.hs-boot
@@ -3,7 +3,7 @@ module GHC.Unit.Types where
import GHC.Prelude ()
import {-# SOURCE #-} GHC.Utils.Outputable
-import {-# SOURCE #-} Language.Haskell.Syntax.ImpExp ( ModuleName )
+import Language.Haskell.Syntax.Module.Name (ModuleName)
import Data.Kind (Type)
data UnitId
diff --git a/compiler/GHC/Utils/Binary.hs b/compiler/GHC/Utils/Binary.hs
index 15071c1b37..5e11489572 100644
--- a/compiler/GHC/Utils/Binary.hs
+++ b/compiler/GHC/Utils/Binary.hs
@@ -77,6 +77,8 @@ module GHC.Utils.Binary
import GHC.Prelude
+import Language.Haskell.Syntax.Module.Name (ModuleName(..))
+
import {-# SOURCE #-} GHC.Types.Name (Name)
import GHC.Data.FastString
import GHC.Utils.Panic.Plain
@@ -1103,6 +1105,10 @@ instance Binary Fingerprint where
put_ h (Fingerprint w1 w2) = do put_ h w1; put_ h w2
get h = do w1 <- get h; w2 <- get h; return (Fingerprint w1 w2)
+instance Binary ModuleName where
+ put_ bh (ModuleName fs) = put_ bh fs
+ get bh = do fs <- get bh; return (ModuleName fs)
+
-- instance Binary FunctionOrData where
-- put_ bh IsFunction = putByte bh 0
-- put_ bh IsData = putByte bh 1
diff --git a/compiler/GHC/Utils/Outputable.hs b/compiler/GHC/Utils/Outputable.hs
index 09575cf53d..6ff57e5775 100644
--- a/compiler/GHC/Utils/Outputable.hs
+++ b/compiler/GHC/Utils/Outputable.hs
@@ -78,6 +78,8 @@ module GHC.Utils.Outputable (
pprFastFilePath, pprFilePathString,
+ pprModuleName,
+
-- * Controlling the style in which output is printed
BindingSite(..),
@@ -104,7 +106,7 @@ module GHC.Utils.Outputable (
) where
-import {-# SOURCE #-} Language.Haskell.Syntax.ImpExp ( ModuleName )
+import Language.Haskell.Syntax.Module.Name ( ModuleName(..) )
import GHC.Prelude
@@ -1039,6 +1041,16 @@ instance Outputable Serialized where
instance Outputable Extension where
ppr = text . show
+instance Outputable ModuleName where
+ ppr = pprModuleName
+
+pprModuleName :: ModuleName -> SDoc
+pprModuleName (ModuleName nm) =
+ getPprStyle $ \ sty ->
+ if codeStyle sty
+ then ztext (zEncodeFS nm)
+ else ftext nm
+
-----------------------------------------------------------------------
-- The @OutputableP@ class
-----------------------------------------------------------------------