diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs index 5d3f43063b00717fa50cf38ba460610998c58891..278c906764998df11b3ab235f0432c85f423283b 100644 --- a/compiler/GHC/Unit/Types.hs +++ b/compiler/GHC/Unit/Types.hs @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-orphans #-} -- instance Data ModuleName - {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveTraversable #-} @@ -117,13 +115,6 @@ data GenModule unit = Module } deriving (Eq,Ord,Data,Functor) --- TODO: should be moved back into Language.Haskell.Syntax.Module.Name -instance Data ModuleName where - -- don't traverse? - toConstr _ = abstractConstr "ModuleName" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "ModuleName" - -- | A Module is a pair of a 'Unit' and a 'ModuleName'. type Module = GenModule Unit diff --git a/compiler/Language/Haskell/Syntax/Module/Name.hs b/compiler/Language/Haskell/Syntax/Module/Name.hs index 632baa61e9c28725c1ecd77776e068ae5ac91a01..85d8c687945b7bcd6c18bf318c6de1ea7140c538 100644 --- a/compiler/Language/Haskell/Syntax/Module/Name.hs +++ b/compiler/Language/Haskell/Syntax/Module/Name.hs @@ -3,6 +3,7 @@ module Language.Haskell.Syntax.Module.Name where import Prelude import Data.Char (isAlphaNum) +import Data.Data import Control.DeepSeq import qualified Text.ParserCombinators.ReadP as Parse import System.FilePath @@ -12,6 +13,14 @@ import GHC.Data.FastString -- | A ModuleName is essentially a simple string, e.g. @Data.List@. newtype ModuleName = ModuleName FastString deriving (Show, Eq) +instance Data ModuleName where + -- don't traverse? + toConstr x = constr + where + constr = mkConstr (dataTypeOf x) "{abstract:ModuleName}" [] Prefix + gunfold _ _ = error "gunfold" + dataTypeOf _ = mkNoRepType "ModuleName" + instance Ord ModuleName where nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2