diff options
46 files changed, 189 insertions, 281 deletions
diff --git a/compiler/basicTypes/Avail.hs b/compiler/basicTypes/Avail.hs index 9e5737f82e..9595abc3ff 100644 --- a/compiler/basicTypes/Avail.hs +++ b/compiler/basicTypes/Avail.hs @@ -2,8 +2,6 @@ -- (c) The University of Glasgow -- -{-# LANGUAGE DeriveDataTypeable #-} - module Avail ( Avails, AvailInfo(..), diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs index 8cec412ab2..df811c954c 100644 --- a/compiler/basicTypes/BasicTypes.hs +++ b/compiler/basicTypes/BasicTypes.hs @@ -235,7 +235,7 @@ unSwap IsSwapped f a b = f b a -} data FunctionOrData = IsFunction | IsData - deriving (Eq, Ord, Data, Typeable) + deriving (Eq, Ord, Data) instance Outputable FunctionOrData where ppr IsFunction = text "(function)" @@ -271,7 +271,7 @@ data StringLiteral = StringLiteral { sl_st :: SourceText, -- literal raw source. -- See not [Literal source text] sl_fs :: FastString -- literal string value - } deriving (Data, Typeable) + } deriving Data instance Eq StringLiteral where (StringLiteral _ a) == (StringLiteral _ b) = a == b @@ -281,7 +281,7 @@ data WarningTxt = WarningTxt (Located SourceText) [Located StringLiteral] | DeprecatedTxt (Located SourceText) [Located StringLiteral] - deriving (Eq, Data, Typeable) + deriving (Eq, Data) instance Outputable WarningTxt where ppr (WarningTxt _ ws) @@ -314,7 +314,7 @@ pprRuleName rn = doubleQuotes (ftext rn) ------------------------ data Fixity = Fixity SourceText Int FixityDirection -- Note [Pragma source text] - deriving (Data, Typeable) + deriving Data instance Outputable Fixity where ppr (Fixity _ prec dir) = hcat [ppr dir, space, int prec] @@ -324,7 +324,7 @@ instance Eq Fixity where -- Used to determine if two fixities conflict ------------------------ data FixityDirection = InfixL | InfixR | InfixN - deriving (Eq, Data, Typeable) + deriving (Eq, Data) instance Outputable FixityDirection where ppr InfixL = text "infixl" @@ -405,7 +405,7 @@ instance Outputable TopLevelFlag where data Boxity = Boxed | Unboxed - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) isBoxed :: Boxity -> Bool isBoxed Boxed = True @@ -425,7 +425,7 @@ instance Outputable Boxity where data RecFlag = Recursive | NonRecursive - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) isRec :: RecFlag -> Bool isRec Recursive = True @@ -453,7 +453,7 @@ instance Outputable RecFlag where data Origin = FromSource | Generated - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) isGenerated :: Origin -> Bool isGenerated Generated = True @@ -486,7 +486,7 @@ instance Outputable Origin where data OverlapFlag = OverlapFlag { overlapMode :: OverlapMode , isSafeOverlap :: Bool - } deriving (Eq, Data, Typeable) + } deriving (Eq, Data) setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag setOverlapModeMaybe f Nothing = f @@ -568,7 +568,7 @@ data OverlapMode -- See Note [Rules for instance lookup] in InstEnv -- instantiating 'b' would change which instance -- was chosen. See also note [Incoherent instances] in InstEnv - deriving (Eq, Data, Typeable) + deriving (Eq, Data) instance Outputable OverlapFlag where @@ -597,7 +597,7 @@ data TupleSort = BoxedTuple | UnboxedTuple | ConstraintTuple - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) tupleSortBoxity :: TupleSort -> Boxity tupleSortBoxity BoxedTuple = Boxed @@ -903,12 +903,12 @@ data Activation = NeverActive -- Active only *strictly before* this phase | ActiveAfter SourceText PhaseNum -- Active in this phase and later - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) -- Eq used in comparing rules in HsDecls data RuleMatchInfo = ConLike -- See Note [CONLIKE pragma] | FunLike - deriving( Eq, Data, Typeable, Show ) + deriving( Eq, Data, Show ) -- Show needed for Lexer.x data InlinePragma -- Note [InlinePragma] @@ -926,7 +926,7 @@ data InlinePragma -- Note [InlinePragma] , inl_act :: Activation -- Says during which phases inlining is allowed , inl_rule :: RuleMatchInfo -- Should the function be treated like a constructor? - } deriving( Eq, Data, Typeable ) + } deriving( Eq, Data ) data InlineSpec -- What the user's INLINE pragma looked like = Inline @@ -934,7 +934,7 @@ data InlineSpec -- What the user's INLINE pragma looked like | NoInline | EmptyInlineSpec -- Used in a place-holder InlinePragma in SpecPrag or IdInfo, -- where there isn't any real inline pragma at all - deriving( Eq, Data, Typeable, Show ) + deriving( Eq, Data, Show ) -- Show needed for Lexer.x {- @@ -1151,7 +1151,7 @@ data FractionalLit = FL { fl_text :: String -- How the value was written in the source , fl_value :: Rational -- Numeric value of the literal } - deriving (Data, Typeable, Show) + deriving (Data, Show) -- The Show instance is required for the derived Lexer.x:Token instance when DEBUG is on negateFractionalLit :: FractionalLit -> FractionalLit diff --git a/compiler/basicTypes/ConLike.hs b/compiler/basicTypes/ConLike.hs index 6fd7731713..53e22fd4bb 100644 --- a/compiler/basicTypes/ConLike.hs +++ b/compiler/basicTypes/ConLike.hs @@ -5,7 +5,7 @@ \section[ConLike]{@ConLike@: Constructor-like things} -} -{-# LANGUAGE CPP, DeriveDataTypeable #-} +{-# LANGUAGE CPP #-} module ConLike ( ConLike(..) @@ -37,7 +37,6 @@ import Var import Type (mkTyConApp) import qualified Data.Data as Data -import qualified Data.Typeable {- ************************************************************************ @@ -50,7 +49,6 @@ import qualified Data.Typeable -- | A constructor-like thing data ConLike = RealDataCon DataCon | PatSynCon PatSyn - deriving Data.Typeable.Typeable {- ************************************************************************ diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index a035202c97..138e5d2b0b 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -80,7 +80,6 @@ import Binary import UniqFM import qualified Data.Data as Data -import qualified Data.Typeable import Data.Char import Data.Word import Data.List( mapAccumL, find ) @@ -415,7 +414,6 @@ data DataCon dcPromoted :: TyCon -- The promoted TyCon -- See Note [Promoted data constructors] in TyCon } - deriving Data.Typeable.Typeable {- Note [TyBinders in DataCons] @@ -510,7 +508,7 @@ data HsSrcBang = HsSrcBang (Maybe SourceText) -- Note [Pragma source text] in BasicTypes SrcUnpackedness SrcStrictness - deriving (Data.Data, Data.Typeable) + deriving Data.Data -- | Bangs of data constructor arguments as generated by the compiler -- after consulting HsSrcBang, flags, etc. @@ -520,19 +518,19 @@ data HsImplBang | HsUnpack (Maybe Coercion) -- ^ Strict and unpacked field -- co :: arg-ty ~ product-ty HsBang - deriving (Data.Data, Data.Typeable) + deriving Data.Data -- | What strictness annotation the user wrote data SrcStrictness = SrcLazy -- ^ Lazy, ie '~' | SrcStrict -- ^ Strict, ie '!' | NoSrcStrict -- ^ no strictness annotation - deriving (Eq, Data.Data, Data.Typeable) + deriving (Eq, Data.Data) -- | What unpackedness the user requested data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified | SrcNoUnpack -- ^ {-# NOUNPACK #-} specified | NoSrcUnpack -- ^ no unpack pragma - deriving (Eq, Data.Data, Data.Typeable) + deriving (Eq, Data.Data) diff --git a/compiler/basicTypes/FieldLabel.hs b/compiler/basicTypes/FieldLabel.hs index 01af19b667..db9e968df0 100644 --- a/compiler/basicTypes/FieldLabel.hs +++ b/compiler/basicTypes/FieldLabel.hs @@ -95,7 +95,7 @@ data FieldLbl a = FieldLabel { -- in the defining module for this datatype? flSelector :: a -- ^ Record selector function } - deriving (Eq, Functor, Foldable, Traversable, Typeable) + deriving (Eq, Functor, Foldable, Traversable) deriving instance Data a => Data (FieldLbl a) instance Outputable a => Outputable (FieldLbl a) where diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index 18b441244c..4d3c23b820 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -61,7 +61,7 @@ import Data.Int import Data.Ratio import Data.Word import Data.Char -import Data.Data ( Data, Typeable ) +import Data.Data ( Data ) import Numeric ( fromRat ) {- @@ -116,7 +116,7 @@ data Literal | LitInteger Integer Type -- ^ Integer literals -- See Note [Integer literals] - deriving (Data, Typeable) + deriving Data {- Note [Integer literals] diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs index 27b4f5e0b1..5755c28501 100644 --- a/compiler/basicTypes/Module.hs +++ b/compiler/basicTypes/Module.hs @@ -9,7 +9,6 @@ These are Uniquable, hence we can build Maps with Modules as the keys. -} -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE MultiParamTypeClasses #-} @@ -234,7 +233,6 @@ addBootSuffixLocn locn -- | A ModuleName is essentially a simple string, e.g. @Data.List@. newtype ModuleName = ModuleName FastString - deriving Typeable instance Uniquable ModuleName where getUnique (ModuleName nm) = getUnique nm @@ -320,7 +318,7 @@ data Module = Module { moduleUnitId :: !UnitId, -- pkg-1.0 moduleName :: !ModuleName -- A.B.C } - deriving (Eq, Ord, Typeable) + deriving (Eq, Ord) instance Uniquable Module where getUnique (Module p n) = getUnique (unitIdFS p `appendFS` moduleNameFS n) @@ -388,7 +386,7 @@ instance DbModuleRep UnitId ModuleName Module where -- it is just the package name, but for user compiled packages, it is a hash. -- ToDo: when the key is a hash, we can do more clever things than store -- the hex representation and hash-cons those strings. -newtype UnitId = PId FastString deriving( Eq, Typeable ) +newtype UnitId = PId FastString deriving Eq -- here to avoid module loops with PackageConfig instance Uniquable UnitId where diff --git a/compiler/basicTypes/Name.hs b/compiler/basicTypes/Name.hs index 26163722b4..7dee877834 100644 --- a/compiler/basicTypes/Name.hs +++ b/compiler/basicTypes/Name.hs @@ -5,7 +5,6 @@ \section[Name]{@Name@: to transmit name info from renamer to typechecker} -} -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE RecordWildCards #-} -- | @@ -109,7 +108,6 @@ data Name = Name { n_uniq :: {-# UNPACK #-} !Int, n_loc :: !SrcSpan -- Definition site } - deriving Typeable -- NOTE: we make the n_loc field strict to eliminate some potential -- (and real!) space leaks, due to the fact that we don't look at diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index e15cfbb775..868fff83b4 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -227,7 +227,6 @@ data OccName = OccName { occNameSpace :: !NameSpace , occNameFS :: !FastString } - deriving Typeable instance Eq OccName where (OccName sp1 s1) == (OccName sp2 s2) = s1 == s2 && sp1 == sp2 @@ -386,7 +385,7 @@ instance Uniquable OccName where getUnique (OccName TcClsName fs) = mkTcOccUnique fs newtype OccEnv a = A (UniqFM a) - deriving (Data, Typeable) + deriving Data emptyOccEnv :: OccEnv a unitOccEnv :: OccName -> a -> OccEnv a diff --git a/compiler/basicTypes/PatSyn.hs b/compiler/basicTypes/PatSyn.hs index e3fdd09dde..5ff99e045c 100644 --- a/compiler/basicTypes/PatSyn.hs +++ b/compiler/basicTypes/PatSyn.hs @@ -5,7 +5,7 @@ \section[PatSyn]{@PatSyn@: Pattern synonyms} -} -{-# LANGUAGE CPP, DeriveDataTypeable #-} +{-# LANGUAGE CPP #-} module PatSyn ( -- * Main data types @@ -34,7 +34,6 @@ import Var import FieldLabel import qualified Data.Data as Data -import qualified Data.Typeable import Data.Function import Data.List @@ -108,7 +107,6 @@ data PatSyn -- => arg_tys -> res_ty -- See Note [Builder for pattern synonyms with unboxed type] } - deriving Data.Typeable.Typeable {- Note [Pattern synonym signatures] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs index ec51ea5516..0856597805 100644 --- a/compiler/basicTypes/RdrName.hs +++ b/compiler/basicTypes/RdrName.hs @@ -136,7 +136,7 @@ data RdrName -- (2) By Template Haskell, when TH has generated a unique name -- -- Such a 'RdrName' can be created by using 'getRdrName' on a 'Name' - deriving (Data, Typeable) + deriving Data {- ************************************************************************ @@ -440,7 +440,7 @@ data GlobalRdrElt , gre_par :: Parent , gre_lcl :: Bool -- ^ True <=> the thing was defined locally , gre_imp :: [ImportSpec] -- ^ In scope through these imports - } deriving (Data, Typeable) + } deriving Data -- INVARIANT: either gre_lcl = True or gre_imp is non-empty -- See Note [GlobalRdrElt provenance] @@ -451,7 +451,7 @@ data Parent = NoParent | FldParent { par_is :: Name, par_lbl :: Maybe FieldLabelString } -- ^ See Note [Parents for record fields] | PatternSynonym - deriving (Eq, Data, Typeable) + deriving (Eq, Data) instance Outputable Parent where ppr NoParent = empty @@ -1020,7 +1020,7 @@ shadowName env name -- It's quite elaborate so that we can give accurate unused-name warnings. data ImportSpec = ImpSpec { is_decl :: ImpDeclSpec, is_item :: ImpItemSpec } - deriving( Eq, Ord, Data, Typeable ) + deriving( Eq, Ord, Data ) -- | Describes a particular import declaration and is -- shared among all the 'Provenance's for that decl @@ -1035,7 +1035,7 @@ data ImpDeclSpec is_as :: ModuleName, -- ^ Import alias, e.g. from @as M@ (or @Muggle@ if there is no @as@ clause) is_qual :: Bool, -- ^ Was this import qualified? is_dloc :: SrcSpan -- ^ The location of the entire import declaration - } deriving (Data, Typeable) + } deriving Data -- | Describes import info a particular Name data ImpItemSpec @@ -1054,7 +1054,7 @@ data ImpItemSpec -- -- Here the constructors of @T@ are not named explicitly; -- only @T@ is named explicitly. - deriving (Data, Typeable) + deriving Data instance Eq ImpDeclSpec where p1 == p2 = case p1 `compare` p2 of EQ -> True; _ -> False diff --git a/compiler/basicTypes/SrcLoc.hs b/compiler/basicTypes/SrcLoc.hs index 2726f41b8b..a5df956b03 100644 --- a/compiler/basicTypes/SrcLoc.hs +++ b/compiler/basicTypes/SrcLoc.hs @@ -226,7 +226,7 @@ data RealSrcSpan srcSpanELine :: {-# UNPACK #-} !Int, srcSpanECol :: {-# UNPACK #-} !Int } - deriving (Eq, Typeable) + deriving Eq -- | A 'SrcSpan' identifies either a specific portion of a text file -- or a human-readable description of a location. @@ -235,8 +235,8 @@ data SrcSpan = | UnhelpfulSpan !FastString -- Just a general indication -- also used to indicate an empty span - deriving (Eq, Ord, Typeable, Show) -- Show is used by Lexer.x, because we - -- derive Show for Token + deriving (Eq, Ord, Show) -- Show is used by Lexer.x, because we + -- derive Show for Token -- | Built-in "bad" 'SrcSpan's for common sources of location uncertainty noSrcSpan, wiredInSrcSpan, interactiveSrcSpan :: SrcSpan @@ -485,7 +485,7 @@ pprUserRealSpan show_path (RealSrcSpan' src_path sline scol eline ecol) -- | We attach SrcSpans to lots of things, so let's have a datatype for it. data GenLocated l e = L l e - deriving (Eq, Ord, Typeable, Data, Functor, Foldable, Traversable) + deriving (Eq, Ord, Data, Functor, Foldable, Traversable) type Located e = GenLocated SrcSpan e type RealLocated e = GenLocated RealSrcSpan e diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index 0af961e80a..8d308ad3e7 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -5,7 +5,7 @@ \section{@Vars@: Variables} -} -{-# LANGUAGE CPP, DeriveDataTypeable, MultiWayIf #-} +{-# LANGUAGE CPP, MultiWayIf #-} -- | -- #name_types# @@ -186,7 +186,6 @@ data Var idScope :: IdScope, id_details :: IdDetails, -- Stable, doesn't change id_info :: IdInfo } -- Unstable, updated by simplifier - deriving Typeable data IdScope -- See Note [GlobalId/LocalId] = GlobalId diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 432f242586..8a34c35e22 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -263,7 +263,7 @@ data Expr b | Tick (Tickish Id) (Expr b) | Type Type | Coercion Coercion - deriving (Data, Typeable) + deriving Data -- | Type synonym for expressions that occur in function argument positions. -- Only 'Arg' should contain a 'Type' at top level, general 'Expr' should not @@ -290,7 +290,7 @@ data AltCon -- See Note [Literal alternatives] | DEFAULT -- ^ Trivial alternative: @case e of { _ -> ... }@ - deriving (Eq, Ord, Data, Typeable) + deriving (Eq, Ord, Data) -- | Binding, used for top level bindings in a module and local bindings in a @let@. @@ -298,7 +298,7 @@ data AltCon -- See Note [GHC Formalism] in coreSyn/CoreLint.hs data Bind b = NonRec b (Expr b) | Rec [(b, (Expr b))] - deriving (Data, Typeable) + deriving Data {- Note [Shadowing] @@ -508,7 +508,7 @@ data Tickish id = -- (uses same names as CCs) } - deriving (Eq, Ord, Data, Typeable) + deriving (Eq, Ord, Data) -- | A "counting tick" (where tickishCounts is True) is one that -- counts evaluations in some way. We cannot discard a counting tick, @@ -729,7 +729,7 @@ data IsOrphan | NotOrphan OccName -- The OccName 'n' witnesses the instance's non-orphanhood -- In that case, the instance is fingerprinted as part -- of the definition of 'n's definition - deriving (Data, Typeable) + deriving Data -- | Returns true if 'IsOrphan' is orphan. isOrphan :: IsOrphan -> Bool diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index ffbd23c459..ce3d3c7d2e 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -74,7 +74,6 @@ data HsLocalBindsLR idL idR | HsIPBinds (HsIPBinds idR) | EmptyLocalBinds - deriving (Typeable) deriving instance (DataId idL, DataId idR) => Data (HsLocalBindsLR idL idR) @@ -98,7 +97,6 @@ data HsValBindsLR idL idR | ValBindsOut [(RecFlag, LHsBinds idL)] [LSig Name] - deriving (Typeable) deriving instance (DataId idL, DataId idR) => Data (HsValBindsLR idL idR) @@ -227,7 +225,6 @@ data HsBindLR idL idR -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId idL, DataId idR) => Data (HsBindLR idL idR) @@ -249,7 +246,7 @@ data ABExport id , abe_wrap :: HsWrapper -- ^ See Note [ABExport wrapper] -- Shape: (forall abs_tvs. abs_ev_vars => abe_mono) ~ abe_poly , abe_prags :: TcSpecPrags -- ^ SPECIALISE pragmas - } deriving (Data, Typeable) + } deriving Data -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnPattern', -- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnLarrow' @@ -263,7 +260,7 @@ data PatSynBind idL idR psb_args :: HsPatSynDetails (Located idR), -- ^ Formal parameter names psb_def :: LPat idR, -- ^ Right-hand side psb_dir :: HsPatSynDir idR -- ^ Directionality - } deriving (Typeable) + } deriving instance (DataId idL, DataId idR) => Data (PatSynBind idL idR) @@ -620,7 +617,6 @@ data HsIPBinds id [LIPBind id] TcEvBinds -- Only in typechecker output; binds -- uses of the implicit parameters - deriving (Typeable) deriving instance (DataId id) => Data (HsIPBinds id) isEmptyIPBinds :: HsIPBinds id -> Bool @@ -644,7 +640,6 @@ type LIPBind id = Located (IPBind id) -- For details on above see note [Api annotations] in ApiAnnotation data IPBind id = IPBind (Either (Located HsIPName) id) (LHsExpr id) - deriving (Typeable) deriving instance (DataId name) => Data (IPBind name) instance (OutputableBndr id) => Outputable (HsIPBinds id) where @@ -794,20 +789,19 @@ data Sig name | MinimalSig SourceText (LBooleanFormula (Located name)) -- Note [Pragma source text] in BasicTypes - deriving (Typeable) deriving instance (DataId name) => Data (Sig name) type LFixitySig name = Located (FixitySig name) data FixitySig name = FixitySig [Located name] Fixity - deriving (Data, Typeable) + deriving Data -- | TsSpecPrags conveys pragmas from the type checker to the desugarer data TcSpecPrags = IsDefaultMethod -- ^ Super-specialised: a default method should -- be macro-expanded at every call site | SpecPrags [LTcSpecPrag] - deriving (Data, Typeable) + deriving Data type LTcSpecPrag = Located TcSpecPrag @@ -818,7 +812,7 @@ data TcSpecPrag InlinePragma -- ^ The Id to be specialised, an wrapper that specialises the -- polymorphic function, and inlining spec for the specialised function - deriving (Data, Typeable) + deriving Data noSpecPrags :: TcSpecPrags noSpecPrags = SpecPrags [] @@ -945,7 +939,7 @@ data HsPatSynDetails a = InfixPatSyn a a | PrefixPatSyn [a] | RecordPatSyn [RecordPatSynField a] - deriving (Typeable, Data) + deriving Data -- See Note [Record PatSyn Fields] @@ -955,7 +949,7 @@ data RecordPatSynField a , recordPatSynPatVar :: a -- Filled in by renamer, the name used internally -- by the pattern - } deriving (Typeable, Data) + } deriving Data @@ -1043,5 +1037,4 @@ data HsPatSynDir id = Unidirectional | ImplicitBidirectional | ExplicitBidirectional (MatchGroup id (LHsExpr id)) - deriving (Typeable) deriving instance (DataId id) => Data (HsPatSynDir id) diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs index dfcb6c16b7..c6026c484e 100644 --- a/compiler/hsSyn/HsDecls.hs +++ b/compiler/hsSyn/HsDecls.hs @@ -142,7 +142,6 @@ data HsDecl id | SpliceD (SpliceDecl id) -- Includes quasi-quotes | DocD (DocDecl) | RoleAnnotD (RoleAnnotDecl id) - deriving (Typeable) deriving instance (DataId id) => Data (HsDecl id) @@ -186,7 +185,7 @@ data HsGroup id hs_vects :: [LVectDecl id], hs_docs :: [LDocDecl] - } deriving (Typeable) + } deriving instance (DataId id) => Data (HsGroup id) emptyGroup, emptyRdrGroup, emptyRnGroup :: HsGroup a @@ -299,14 +298,13 @@ instance OutputableBndr name => Outputable (HsGroup name) where data SpliceExplicitFlag = ExplicitSplice | -- <=> $(f x y) ImplicitSplice -- <=> f x y, i.e. a naked top level expression - deriving (Data, Typeable) + deriving Data type LSpliceDecl name = Located (SpliceDecl name) data SpliceDecl id = SpliceDecl -- Top level splice (Located (HsSplice id)) SpliceExplicitFlag - deriving (Typeable) deriving instance (DataId id) => Data (SpliceDecl id) instance OutputableBndr name => Outputable (SpliceDecl name) where @@ -522,7 +520,6 @@ data TyClDecl name -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId id) => Data (TyClDecl id) @@ -749,7 +746,6 @@ data TyClGroup name -- See Note [TyClGroups and dependency analysis] = TyClGroup { group_tyclds :: [LTyClDecl name] , group_roles :: [LRoleAnnotDecl name] , group_instds :: [LInstDecl name] } - deriving (Typeable) deriving instance (DataId id) => Data (TyClGroup id) emptyTyClGroup :: TyClGroup name @@ -863,7 +859,6 @@ data FamilyResultSig name = -- see Note [FamilyResultSig] -- For details on above see note [Api annotations] in ApiAnnotation - deriving ( Typeable ) deriving instance (DataId name) => Data (FamilyResultSig name) type LFamilyDecl name = Located (FamilyDecl name) @@ -882,7 +877,6 @@ data FamilyDecl name = FamilyDecl -- 'ApiAnnotation.AnnVbar' -- For details on above see note [Api annotations] in ApiAnnotation - deriving ( Typeable ) deriving instance (DataId id) => Data (FamilyDecl id) @@ -902,7 +896,7 @@ data InjectivityAnn name -- 'ApiAnnotation.AnnRarrow', 'ApiAnnotation.AnnVbar' -- For details on above see note [Api annotations] in ApiAnnotation - deriving ( Data, Typeable ) + deriving Data data FamilyInfo name = DataFamily @@ -910,7 +904,6 @@ data FamilyInfo name -- | 'Nothing' if we're in an hs-boot file and the user -- said "type family Foo x where .." | ClosedTypeFamily (Maybe [LTyFamInstEqn name]) - deriving( Typeable ) deriving instance (DataId name) => Data (FamilyInfo name) -- | Does this family declaration have a complete, user-supplied kind signature? @@ -1015,7 +1008,6 @@ data HsDataDefn name -- The payload of a data type defn -- For details on above see note [Api annotations] in ApiAnnotation } - deriving( Typeable ) deriving instance (DataId id) => Data (HsDataDefn id) type HsDeriving name = Maybe (Located [LHsSigType name]) @@ -1039,7 +1031,7 @@ type HsDeriving name = Maybe (Located [LHsSigType name]) data NewOrData = NewType -- ^ @newtype Blah ...@ | DataType -- ^ @data Blah ...@ - deriving( Eq, Data, Typeable ) -- Needed because Demand derives Eq + deriving( Eq, Data ) -- Needed because Demand derives Eq type LConDecl name = Located (ConDecl name) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when @@ -1097,7 +1089,7 @@ data ConDecl name , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. - } deriving (Typeable) + } deriving instance (DataId name) => Data (ConDecl name) type HsConDeclDetails name @@ -1281,7 +1273,6 @@ data TyFamEqn name pats -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual' -- For details on above see note [Api annotations] in ApiAnnotation - deriving( Typeable ) deriving instance (DataId name, Data pats) => Data (TyFamEqn name pats) type LTyFamInstDecl name = Located (TyFamInstDecl name) @@ -1294,7 +1285,6 @@ data TyFamInstDecl name -- 'ApiAnnotation.AnnInstance', -- For details on above see note [Api annotations] in ApiAnnotation - deriving( Typeable ) deriving instance (DataId name) => Data (TyFamInstDecl name) ----------------- Data family instances ------------- @@ -1314,7 +1304,6 @@ data DataFamInstDecl name -- 'ApiAnnotation.AnnClose' -- For details on above see note [Api annotations] in ApiAnnotation - deriving( Typeable ) deriving instance (DataId name) => Data (DataFamInstDecl name) @@ -1342,7 +1331,6 @@ data ClsInstDecl name -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose', -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId id) => Data (ClsInstDecl id) @@ -1356,7 +1344,6 @@ data InstDecl name -- Both class and family instances { dfid_inst :: DataFamInstDecl name } | TyFamInstD -- type family instance { tfid_inst :: TyFamInstDecl name } - deriving (Typeable) deriving instance (DataId id) => Data (InstDecl id) instance (OutputableBndr name) => Outputable (TyFamInstDecl name) where @@ -1471,7 +1458,6 @@ data DerivDecl name = DerivDecl -- For details on above see note [Api annotations] in ApiAnnotation } - deriving (Typeable) deriving instance (DataId name) => Data (DerivDecl name) instance (OutputableBndr name) => Outputable (DerivDecl name) where @@ -1498,7 +1484,6 @@ data DefaultDecl name -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (DefaultDecl name) instance (OutputableBndr name) @@ -1541,7 +1526,6 @@ data ForeignDecl name -- 'ApiAnnotation.AnnDcolon' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (ForeignDecl name) {- @@ -1582,7 +1566,7 @@ data ForeignImport = -- import of a C entity CImportSpec -- details of the C entity (Located SourceText) -- original source text for -- the C entity - deriving (Data, Typeable) + deriving Data -- details of an external C entity -- @@ -1590,7 +1574,7 @@ data CImportSpec = CLabel CLabelString -- import address of a C label | CFunction CCallTarget -- static or dynamic function | CWrapper -- wrapper to expose closures -- (former f.e.d.) - deriving (Data, Typeable) + deriving Data -- specification of an externally exported entity in dependence on the calling -- convention @@ -1599,7 +1583,7 @@ data ForeignExport = CExport (Located CExportSpec) -- contains the calling -- convention (Located SourceText) -- original source text for -- the C entity - deriving (Data, Typeable) + deriving Data -- pretty printing of foreign declarations -- @@ -1649,7 +1633,6 @@ type LRuleDecls name = Located (RuleDecls name) -- Note [Pragma source text] in BasicTypes data RuleDecls name = HsRules { rds_src :: SourceText , rds_rules :: [LRuleDecl name] } - deriving (Typeable) deriving instance (DataId name) => Data (RuleDecls name) type LRuleDecl name = Located (RuleDecl name) @@ -1674,7 +1657,6 @@ data RuleDecl name -- 'ApiAnnotation.AnnEqual', -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (RuleDecl name) flattenRuleDecls :: [LRuleDecls name] -> [LRuleDecl name] @@ -1689,7 +1671,6 @@ data RuleBndr name -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (RuleBndr name) collectRuleBndrSigTys :: [RuleBndr name] -> [LHsSigWcType name] @@ -1777,7 +1758,6 @@ data VectDecl name (LHsSigType name) | HsVectInstOut -- post type-checking (always SCALAR) !!!FIXME: should be superfluous now ClsInst - deriving (Typeable) deriving instance (DataId name) => Data (VectDecl name) lvectDeclName :: NamedThing name => LVectDecl name -> Name @@ -1844,7 +1824,7 @@ data DocDecl | DocCommentPrev HsDocString | DocCommentNamed String HsDocString | DocGroup Int HsDocString - deriving (Data, Typeable) + deriving Data -- Okay, I need to reconstruct the document comments, but for now: instance Outputable DocDecl where @@ -1873,13 +1853,13 @@ type LWarnDecls name = Located (WarnDecls name) data WarnDecls name = Warnings { wd_src :: SourceText , wd_warnings :: [LWarnDecl name] } - deriving (Data, Typeable) + deriving Data type LWarnDecl name = Located (WarnDecl name) data WarnDecl name = Warning [Located name] WarningTxt - deriving (Data, Typeable) + deriving Data instance OutputableBndr name => Outputable (WarnDecls name) where ppr (Warnings _ decls) = ppr decls @@ -1907,7 +1887,6 @@ data AnnDecl name = HsAnnotation -- 'ApiAnnotation.AnnClose' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (AnnDecl name) instance (OutputableBndr name) => Outputable (AnnDecl name) where @@ -1917,7 +1896,7 @@ instance (OutputableBndr name) => Outputable (AnnDecl name) where data AnnProvenance name = ValueAnnProvenance (Located name) | TypeAnnProvenance (Located name) | ModuleAnnProvenance - deriving (Data, Typeable, Functor) + deriving (Data, Functor) deriving instance Foldable AnnProvenance deriving instance Traversable AnnProvenance @@ -1952,7 +1931,7 @@ data RoleAnnotDecl name -- 'ApiAnnotation.AnnRole' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Data, Typeable) + deriving Data instance OutputableBndr name => Outputable (RoleAnnotDecl name) where ppr (RoleAnnotDecl ltycon roles) diff --git a/compiler/hsSyn/HsDoc.hs b/compiler/hsSyn/HsDoc.hs index 72bf0e56a4..e5159363d7 100644 --- a/compiler/hsSyn/HsDoc.hs +++ b/compiler/hsSyn/HsDoc.hs @@ -15,7 +15,7 @@ import FastString import Data.Data newtype HsDocString = HsDocString FastString - deriving (Eq, Show, Data, Typeable) + deriving (Eq, Show, Data) type LHsDocString = Located HsDocString diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs index a6aaa6cecd..0937d29f65 100644 --- a/compiler/hsSyn/HsExpr.hs +++ b/compiler/hsSyn/HsExpr.hs @@ -95,7 +95,6 @@ noPostTcTable = [] data SyntaxExpr id = SyntaxExpr { syn_expr :: HsExpr id , syn_arg_wraps :: [HsWrapper] , syn_res_wrap :: HsWrapper } - deriving (Typeable) deriving instance (DataId id) => Data (SyntaxExpr id) -- | This is used for rebindable-syntax pieces that are too polymorphic @@ -179,7 +178,7 @@ data UnboundVar | TrueExprHole OccName -- ^ A "true" expression hole (_ or _x) - deriving (Data, Typeable) + deriving Data instance Outputable UnboundVar where ppr = ppr . unboundVarOcc @@ -658,7 +657,6 @@ data HsExpr id | HsWrap HsWrapper -- TRANSLATION (HsExpr id) - deriving (Typeable) deriving instance (DataId id) => Data (HsExpr id) -- | HsTupArg is used for tuple sections @@ -671,7 +669,6 @@ type LHsTupArg id = Located (HsTupArg id) data HsTupArg id = Present (LHsExpr id) -- ^ The argument | Missing (PostTc id Type) -- ^ The argument is missing, but this is its type - deriving (Typeable) deriving instance (DataId id) => Data (HsTupArg id) tupArgPresent :: LHsTupArg id -> Bool @@ -1143,11 +1140,10 @@ data HsCmd id (HsCmd id) -- If cmd :: arg1 --> res -- wrap :: arg1 "->" arg2 -- Then (HsCmdWrap wrap cmd) :: arg2 --> res - deriving (Typeable) deriving instance (DataId id) => Data (HsCmd id) data HsArrAppType = HsHigherOrderApp | HsFirstOrderApp - deriving (Data, Typeable) + deriving Data {- | Top-level command, introducing a new arrow. @@ -1162,7 +1158,6 @@ data HsCmdTop id (PostTc id Type) -- Nested tuple of inputs on the command's stack (PostTc id Type) -- return type of the command (CmdSyntaxTable id) -- See Note [CmdSyntaxTable] - deriving (Typeable) deriving instance (DataId id) => Data (HsCmdTop id) instance OutputableBndr id => Outputable (HsCmd id) where @@ -1291,7 +1286,6 @@ data MatchGroup id body -- The type is the type of the entire group -- t1 -> ... -> tn -> tr -- where there are n patterns - deriving (Typeable) deriving instance (Data body,DataId id) => Data (MatchGroup id body) type LMatch id body = Located (Match id body) @@ -1309,7 +1303,7 @@ data Match id body -- Nothing after typechecking -- NB: No longer supported m_grhss :: (GRHSs id body) - } deriving (Typeable) + } deriving instance (Data body,DataId id) => Data (Match id body) {- @@ -1344,7 +1338,6 @@ data MatchFixity id = NonFunBindMatch | FunBindMatch (Located id) -- of the Id Bool -- is infix - deriving (Typeable) deriving instance (DataId id) => Data (MatchFixity id) isInfixMatch :: Match id body -> Bool @@ -1386,7 +1379,7 @@ data GRHSs id body = GRHSs { grhssGRHSs :: [LGRHS id body], -- ^ Guarded RHSs grhssLocalBinds :: Located (HsLocalBinds id) -- ^ The where clause - } deriving (Typeable) + } deriving instance (Data body,DataId id) => Data (GRHSs id body) type LGRHS id body = Located (GRHS id body) @@ -1394,7 +1387,6 @@ type LGRHS id body = Located (GRHS id body) -- | Guarded Right Hand Side. data GRHS id body = GRHS [GuardLStmt id] -- Guards body -- Right hand side - deriving (Typeable) deriving instance (Data body,DataId id) => Data (GRHS id body) -- We know the list must have at least one @Match@ in it. @@ -1623,21 +1615,19 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- With rebindable syntax the type might not -- be quite as simple as (m (tya, tyb, tyc)). } - deriving (Typeable) deriving instance (Data body, DataId idL, DataId idR) => Data (StmtLR idL idR body) data TransForm -- The 'f' below is the 'using' function, 'e' is the by function = ThenForm -- then f or then f by e (depending on trS_by) | GroupForm -- then group using f or then group by e using f (depending on trS_by) - deriving (Data, Typeable) + deriving Data data ParStmtBlock idL idR = ParStmtBlock [ExprLStmt idL] [idR] -- The variables to be returned (SyntaxExpr idR) -- The return operator - deriving( Typeable ) deriving instance (DataId idL, DataId idR) => Data (ParStmtBlock idL idR) data ApplicativeArg idL idR @@ -1648,7 +1638,6 @@ data ApplicativeArg idL idR [ExprLStmt idL] -- stmts (HsExpr idL) -- return (v1,..,vn), or just (v1,..,vn) (LPat idL) -- (v1,...,vn) - deriving( Typeable ) deriving instance (DataId idL, DataId idR) => Data (ApplicativeArg idL idR) {- @@ -1930,7 +1919,6 @@ data HsSplice id id -- Quoter SrcSpan -- The span of the enclosed string FastString -- The enclosed string - deriving (Typeable ) deriving instance (DataId id) => Data (HsSplice id) @@ -1943,18 +1931,18 @@ type SplicePointName = Name data PendingRnSplice = PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr Name) - deriving (Data, Typeable) + deriving Data data UntypedSpliceFlavour = UntypedExpSplice | UntypedPatSplice | UntypedTypeSplice | UntypedDeclSplice - deriving( Data, Typeable ) + deriving Data data PendingTcSplice = PendingTcSplice SplicePointName (LHsExpr Id) - deriving( Data, Typeable ) + deriving Data {- @@ -2058,7 +2046,6 @@ data HsBracket id = ExpBr (LHsExpr id) -- [| expr |] | VarBr Bool id -- True: 'x, False: ''T -- (The Bool flag is used only in pprHsBracket) | TExpBr (LHsExpr id) -- [|| expr ||] - deriving (Typeable) deriving instance (DataId id) => Data (HsBracket id) isTypedBracket :: HsBracket id -> Bool @@ -2109,7 +2096,6 @@ data ArithSeqInfo id | FromThenTo (LHsExpr id) (LHsExpr id) (LHsExpr id) - deriving (Typeable) deriving instance (DataId id) => Data (ArithSeqInfo id) instance OutputableBndr id => Outputable (ArithSeqInfo id) where @@ -2148,7 +2134,7 @@ data HsMatchContext id -- Context of a Match | ThPatSplice -- A Template Haskell pattern splice | ThPatQuote -- A Template Haskell pattern quotation [p| (a,b) |] | PatSyn -- A pattern synonym declaration - deriving (Data, Typeable) + deriving Data data HsStmtContext id = ListComp @@ -2163,7 +2149,7 @@ data HsStmtContext id | PatGuard (HsMatchContext id) -- Pattern guard for specified thing | ParStmtCtxt (HsStmtContext id) -- A branch of a parallel stmt | TransStmtCtxt (HsStmtContext id) -- A branch of a transform stmt - deriving (Data, Typeable) + deriving Data isListCompExpr :: HsStmtContext id -> Bool -- Uses syntax [ e | quals ] diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/hsSyn/HsImpExp.hs index 4c72b35699..beecd60398 100644 --- a/compiler/hsSyn/HsImpExp.hs +++ b/compiler/hsSyn/HsImpExp.hs @@ -70,7 +70,7 @@ data ImportDecl name -- to location in ideclHiding -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Data, Typeable) + deriving Data simpleImportDecl :: ModuleName -> ImportDecl name simpleImportDecl mn = ImportDecl { @@ -177,9 +177,9 @@ data IE name | IEGroup Int HsDocString -- ^ Doc section heading | IEDoc HsDocString -- ^ Some documentation | IEDocNamed String -- ^ Reference to named doc - deriving (Eq, Data, Typeable) + deriving (Eq, Data) -data IEWildcard = NoIEWildcard | IEWildcard Int deriving (Eq, Data, Typeable) +data IEWildcard = NoIEWildcard | IEWildcard Int deriving (Eq, Data) {- Note [IEThingWith] diff --git a/compiler/hsSyn/HsLit.hs b/compiler/hsSyn/HsLit.hs index 4686077d27..4fa0a64afd 100644 --- a/compiler/hsSyn/HsLit.hs +++ b/compiler/hsSyn/HsLit.hs @@ -57,7 +57,7 @@ data HsLit -- done with HsOverLit) | HsFloatPrim FractionalLit -- Unboxed Float | HsDoublePrim FractionalLit -- Unboxed Double - deriving (Data, Typeable) + deriving Data instance Eq HsLit where (HsChar _ x1) == (HsChar _ x2) = x1==x2 @@ -81,7 +81,6 @@ data HsOverLit id -- An overloaded literal ol_rebindable :: PostRn id Bool, -- Note [ol_rebindable] ol_witness :: HsExpr id, -- Note [Overloaded literal witnesses] ol_type :: PostTc id Type } - deriving (Typeable) deriving instance (DataId id) => Data (HsOverLit id) -- Note [Literal source text] in BasicTypes for SourceText fields in @@ -90,7 +89,7 @@ data OverLitVal = HsIntegral !SourceText !Integer -- Integer-looking literals; | HsFractional !FractionalLit -- Frac-looking literals | HsIsString !SourceText !FastString -- String-looking literals - deriving (Data, Typeable) + deriving Data overLitType :: HsOverLit a -> PostTc a Type overLitType = ol_type diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index e01c6b9d07..c168def337 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -228,7 +228,6 @@ data Pat id Type -- Type of whole pattern, t1 -- During desugaring a (CoPat co pat) turns into a cast with 'co' on -- the scrutinee, followed by a match on 'pat' - deriving (Typeable) deriving instance (DataId id) => Data (Pat id) type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id)) @@ -246,7 +245,7 @@ data HsRecFields id arg -- A bunch of record fields -- Used for both expressions and patterns = HsRecFields { rec_flds :: [LHsRecField id arg], rec_dotdot :: Maybe Int } -- Note [DotDot fields] - deriving (Typeable, Functor, Foldable, Traversable) + deriving (Functor, Foldable, Traversable) deriving instance (DataId id, Data arg) => Data (HsRecFields id arg) @@ -278,7 +277,7 @@ data HsRecField' id arg = HsRecField { hsRecFieldLbl :: Located id, hsRecFieldArg :: arg, -- ^ Filled in by renamer when punning hsRecPun :: Bool -- ^ Note [Punning] - } deriving (Data, Typeable, Functor, Foldable, Traversable) + } deriving (Data, Functor, Foldable, Traversable) -- Note [Punning] diff --git a/compiler/hsSyn/HsSyn.hs b/compiler/hsSyn/HsSyn.hs index c226dfecf9..76d31a4182 100644 --- a/compiler/hsSyn/HsSyn.hs +++ b/compiler/hsSyn/HsSyn.hs @@ -105,7 +105,6 @@ data HsModule name -- hsmodImports,hsmodDecls if this style is used. -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (HsModule name) instance (OutputableBndr name, HasOccName name) diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index bc78a7d270..66145b6588 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -251,7 +251,6 @@ data LHsQTyVars name -- See Note [HsType binders] -- which explicit vars are dependent -- See Note [Dependent LHsQTyVars] in TcHsType } - deriving( Typeable ) deriving instance (DataId name) => Data (LHsQTyVars name) @@ -282,7 +281,6 @@ data HsImplicitBndrs name thing -- See Note [HsType binders] = HsIB { hsib_vars :: PostRn name [Name] -- Implicitly-bound kind & type vars , hsib_body :: thing -- Main payload (type or list of types) } - deriving (Typeable) data HsWildCardBndrs name thing -- See Note [HsType binders] @@ -300,7 +298,6 @@ data HsWildCardBndrs name thing , hswc_body :: thing -- Main payload (type or list of types) } - deriving( Typeable ) deriving instance (Data name, Data thing, Data (PostRn name [Name])) => Data (HsImplicitBndrs name thing) @@ -372,7 +369,7 @@ mkEmptyWildCardBndrs x = HsWC { hswc_body = x -- | These names are used early on to store the names of implicit -- parameters. They completely disappear after type-checking. newtype HsIPName = HsIPName FastString - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) hsIPNameFS :: HsIPName -> FastString hsIPNameFS (HsIPName n) = n @@ -398,7 +395,6 @@ data HsTyVarBndr name -- 'ApiAnnotation.AnnDcolon', 'ApiAnnotation.AnnClose' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (HsTyVarBndr name) -- | Does this 'HsTyVarBndr' come with an explicit kind annotation? @@ -565,7 +561,6 @@ data HsType name -- ^ - 'ApiAnnotation.AnnKeywordId' : None -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (HsType name) -- Note [Literal source text] in BasicTypes for SourceText fields in @@ -573,13 +568,12 @@ deriving instance (DataId name) => Data (HsType name) data HsTyLit = HsNumTy SourceText Integer | HsStrTy SourceText FastString - deriving (Data, Typeable) + deriving Data newtype HsWildCardInfo name -- See Note [The wildcard story for types] = AnonWildCard (PostRn name (Located Name)) -- A anonymous wild card ('_'). A fresh Name is generated for -- each individual anonymous wildcard during renaming - deriving (Typeable) deriving instance (DataId name) => Data (HsWildCardInfo name) type LHsAppType name = Located (HsAppType name) @@ -588,7 +582,6 @@ type LHsAppType name = Located (HsAppType name) data HsAppType name = HsAppInfix (Located name) -- either a symbol or an id in backticks | HsAppPrefix (LHsType name) -- anything else, including things like (+) - deriving (Typeable) deriving instance (DataId name) => Data (HsAppType name) instance OutputableBndr name => Outputable (HsAppType name) where @@ -705,7 +698,7 @@ data HsTupleSort = HsUnboxedTuple | HsBoxedTuple | HsConstraintTuple | HsBoxedOrConstraintTuple - deriving (Data, Typeable) + deriving Data type LConDeclField name = Located (ConDeclField name) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when @@ -720,7 +713,6 @@ data ConDeclField name -- Record fields have Haddoc docs on them -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' -- For details on above see note [Api annotations] in ApiAnnotation - deriving (Typeable) deriving instance (DataId name) => Data (ConDeclField name) instance (OutputableBndr name) => Outputable (ConDeclField name) where @@ -732,7 +724,7 @@ data HsConDetails arg rec = PrefixCon [arg] -- C p1 p2 p3 | RecCon rec -- C { x = p1, y = p2 } | InfixCon arg arg -- p1 `C` p2 - deriving (Data, Typeable) + deriving Data instance (Outputable arg, Outputable rec) => Outputable (HsConDetails arg rec) where @@ -1050,7 +1042,6 @@ data FieldOcc name = FieldOcc { rdrNameFieldOcc :: Located RdrName -- ^ See Note [Located RdrNames] in HsExpr , selectorFieldOcc :: PostRn name name } - deriving Typeable deriving instance Eq (PostRn name name) => Eq (FieldOcc name) deriving instance Ord (PostRn name name) => Ord (FieldOcc name) deriving instance (Data name, Data (PostRn name name)) => Data (FieldOcc name) @@ -1075,7 +1066,6 @@ mkFieldOcc rdr = FieldOcc rdr PlaceHolder data AmbiguousFieldOcc name = Unambiguous (Located RdrName) (PostRn name name) | Ambiguous (Located RdrName) (PostTc name name) - deriving (Typeable) deriving instance ( Data name , Data (PostRn name name) , Data (PostTc name name)) diff --git a/compiler/hsSyn/PlaceHolder.hs b/compiler/hsSyn/PlaceHolder.hs index b4e109f045..cacad7111c 100644 --- a/compiler/hsSyn/PlaceHolder.hs +++ b/compiler/hsSyn/PlaceHolder.hs @@ -35,7 +35,7 @@ import BasicTypes (Fixity) -- | used as place holder in PostTc and PostRn values data PlaceHolder = PlaceHolder - deriving (Data,Typeable) + deriving (Data) -- | Types that are not defined until after type checking type family PostTc id ty -- Note [Pass sensitive types] diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index e7673d6ab4..53e40413ef 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -4,7 +4,7 @@ \section[HscTypes]{Types for the per-module compiler} -} -{-# LANGUAGE CPP, DeriveDataTypeable, ScopedTypeVariables #-} +{-# LANGUAGE CPP, ScopedTypeVariables #-} -- | Types for the per-module compiler module HscTypes ( @@ -194,7 +194,6 @@ import Foreign import Control.Monad ( guard, liftM, when, ap ) import Data.IORef import Data.Time -import Data.Typeable ( Typeable ) import Exception import System.FilePath #ifdef GHCI @@ -286,7 +285,6 @@ throwOneError err = liftIO $ throwIO $ mkSrcErr $ unitBag err -- See 'printExceptionAndWarnings' for more information on what to take care -- of when writing a custom error handler. newtype SourceError = SourceError ErrorMessages - deriving Typeable instance Show SourceError where show (SourceError msgs) = unlines . map show . bagToList $ msgs @@ -304,7 +302,6 @@ handleSourceError handler act = -- | An error thrown if the GHC API is used in an incorrect fashion. newtype GhcApiError = GhcApiError String - deriving Typeable instance Show GhcApiError where show (GhcApiError msg) = msg diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs index 6d08b0058c..eebec547cc 100644 --- a/compiler/parser/ApiAnnotation.hs +++ b/compiler/parser/ApiAnnotation.hs @@ -278,7 +278,7 @@ data AnnKeywordId | AnnRarrowtail -- ^ '>>-' | AnnRarrowtailU -- ^ '>>-', unicode variant | AnnEofPos - deriving (Eq, Ord, Data, Typeable, Show) + deriving (Eq, Ord, Data, Show) instance Outputable AnnKeywordId where ppr x = text (show x) @@ -294,7 +294,7 @@ data AnnotationComment = | AnnDocOptions String -- ^ doc options (prune, ignore-exports, etc) | AnnLineComment String -- ^ comment starting by "--" | AnnBlockComment String -- ^ comment in {- -} - deriving (Eq, Ord, Data, Typeable, Show) + deriving (Eq, Ord, Data, Show) -- Note: these are based on the Token versions, but the Token type is -- defined in Lexer.x and bringing it in here would create a loop @@ -314,7 +314,7 @@ type LRdrName = Located RdrName -- original source representation can be reproduced in the corresponding -- 'ApiAnnotation' data IsUnicodeSyntax = UnicodeSyntax | NormalSyntax - deriving (Eq, Ord, Data, Typeable, Show) + deriving (Eq, Ord, Data, Show) -- | Convert a normal annotation into its unicode equivalent one unicodeAnn :: AnnKeywordId -> AnnKeywordId @@ -338,4 +338,4 @@ unicodeAnn ann = ann -- -- This type indicates whether the 'e' is present or not. data HasE = HasE | NoE - deriving (Eq, Ord, Data, Typeable, Show) + deriving (Eq, Ord, Data, Show) diff --git a/compiler/prelude/ForeignCall.hs b/compiler/prelude/ForeignCall.hs index f23436bda6..f26298f174 100644 --- a/compiler/prelude/ForeignCall.hs +++ b/compiler/prelude/ForeignCall.hs @@ -62,7 +62,7 @@ data Safety | PlayRisky -- None of the above can happen; the call will return -- without interacting with the runtime system at all - deriving ( Eq, Show, Data, Typeable ) + deriving ( Eq, Show, Data ) -- Show used just for Show Lex.Token, I think {-! derive: Binary !-} @@ -94,7 +94,7 @@ data CExportSpec -- See note [Pragma source text] in BasicTypes CLabelString -- C Name of exported function CCallConv - deriving (Data, Typeable) + deriving Data {-! derive: Binary !-} data CCallSpec @@ -129,7 +129,7 @@ data CCallTarget -- allowed in CAPI imports | DynamicTarget - deriving( Eq, Data, Typeable ) + deriving( Eq, Data ) {-! derive: Binary !-} isDynamicTarget :: CCallTarget -> Bool @@ -150,7 +150,7 @@ See: http://www.programmersheaven.com/2/Calling-conventions -- any changes here should be replicated in the CallConv type in template haskell data CCallConv = CCallConv | CApiConv | StdCallConv | PrimCallConv | JavaScriptCallConv - deriving (Eq, Data, Typeable) + deriving (Eq, Data) {-! derive: Binary !-} instance Outputable CCallConv where @@ -224,7 +224,7 @@ instance Outputable CCallSpec where -- The filename for a C header file -- Note [Pragma source text] in BasicTypes data Header = Header SourceText FastString - deriving (Eq, Data, Typeable) + deriving (Eq, Data) instance Outputable Header where ppr (Header _ h) = quotes $ ppr h @@ -239,7 +239,7 @@ instance Outputable Header where data CType = CType SourceText -- Note [Pragma source text] in BasicTypes (Maybe Header) -- header to include for this type (SourceText,FastString) -- the type itself - deriving (Eq, Data, Typeable) + deriving (Eq, Data) instance Outputable CType where ppr (CType _ mh (_,ct)) = hDoc <+> ftext ct diff --git a/compiler/profiling/CostCentre.hs b/compiler/profiling/CostCentre.hs index 03cde88786..4dd54dcc6c 100644 --- a/compiler/profiling/CostCentre.hs +++ b/compiler/profiling/CostCentre.hs @@ -60,12 +60,12 @@ data CostCentre cc_mod :: Module, -- Name of module defining this CC. cc_loc :: SrcSpan } - deriving (Data, Typeable) + deriving Data type CcName = FastString data IsCafCC = NotCafCC | CafCC - deriving (Eq, Ord, Data, Typeable) + deriving (Eq, Ord, Data) instance Eq CostCentre where diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 271652a40d..b53fa65dc9 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1625,10 +1625,10 @@ be satisfied too. But not always; consider: The derived instance for (Ord (T a)) must have a (Num a) constraint! Similarly consider: - data T a = MkT deriving( Data, Typeable ) + data T a = MkT deriving( Data ) Here there *is* no argument field, but we must nevertheless generate a context for the Data instances: - instance Typable a => Data (T a) where ... + instance Typeable a => Data (T a) where ... ************************************************************************ * * diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index b86e3f4678..f54ff5723f 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -186,7 +186,7 @@ data HsWrapper | WpLet TcEvBinds -- Non-empty (or possibly non-empty) evidence bindings, -- so that the identity coercion is always exactly WpHole - deriving (Data.Data, Data.Typeable) + deriving Data.Data (<.>) :: HsWrapper -> HsWrapper -> HsWrapper @@ -283,8 +283,6 @@ data TcEvBinds | EvBinds -- Immutable after zonking (Bag EvBind) - deriving( Data.Typeable ) - data EvBindsVar = EvBindsVar (IORef EvBindMap) Unique -- The Unique is for debug printing only @@ -381,7 +379,7 @@ data EvTerm | EvTypeable Type EvTypeable -- Dictionary for (Typeable ty) - deriving( Data.Data, Data.Typeable ) + deriving Data.Data -- | Instructions on how to make a 'Typeable' dictionary. @@ -400,12 +398,12 @@ data EvTypeable -- The 'EvTerm' is evidence of, e.g., @KnownNat 3@ -- (see Trac #10348) - deriving ( Data.Data, Data.Typeable ) + deriving Data.Data data EvLit = EvNum Integer | EvStr FastString - deriving( Data.Data, Data.Typeable ) + deriving Data.Data -- | Evidence for @CallStack@ implicit parameters. data EvCallStack @@ -414,7 +412,7 @@ data EvCallStack | EvCsPushCall Name RealSrcSpan EvTerm -- ^ @EvCsPushCall name loc stk@ represents a call to @name@, occurring at -- @loc@, in a calling context @stk@. - deriving( Data.Data, Data.Typeable ) + deriving Data.Data {- Note [Typeable evidence terms] diff --git a/compiler/types/Class.hs b/compiler/types/Class.hs index d62f90f09d..93cc72ff88 100644 --- a/compiler/types/Class.hs +++ b/compiler/types/Class.hs @@ -3,7 +3,7 @@ -- -- The @Class@ datatype -{-# LANGUAGE CPP, DeriveDataTypeable #-} +{-# LANGUAGE CPP #-} module Class ( Class, @@ -36,7 +36,6 @@ import PrelNames ( eqTyConKey, coercibleTyConKey, typeableClassKey, import Outputable import BooleanFormula (BooleanFormula) -import Data.Typeable (Typeable) import qualified Data.Data as Data {- @@ -79,7 +78,6 @@ data Class -- Minimal complete definition classMinimalDef :: ClassMinimalDef } - deriving Typeable -- | e.g. -- diff --git a/compiler/types/CoAxiom.hs b/compiler/types/CoAxiom.hs index fd5187c94f..fb1b4fffb2 100644 --- a/compiler/types/CoAxiom.hs +++ b/compiler/types/CoAxiom.hs @@ -124,16 +124,13 @@ type BranchIndex = Int -- The index of the branch in the list of branches -- promoted data type data BranchFlag = Branched | Unbranched type Branched = 'Branched -deriving instance Typeable 'Branched type Unbranched = 'Unbranched -deriving instance Typeable 'Unbranched -- By using type synonyms for the promoted constructors, we avoid needing -- DataKinds and the promotion quote in client modules. This also means that -- we don't need to export the term-level constructors, which should never be used. newtype Branches (br :: BranchFlag) = MkBranches { unMkBranches :: Array BranchIndex CoAxBranch } - deriving Typeable type role Branches nominal manyBranches :: [CoAxBranch] -> Branches Branched @@ -216,7 +213,6 @@ data CoAxiom br -- See Note [Implicit axioms] -- INVARIANT: co_ax_implicit == True implies length co_ax_branches == 1. } - deriving Typeable data CoAxBranch = CoAxBranch @@ -235,7 +231,7 @@ data CoAxBranch , cab_incomps :: [CoAxBranch] -- The previous incompatible branches -- See Note [Storing compatibility] } - deriving ( Data.Data, Data.Typeable ) + deriving Data.Data toBranchedAxiom :: CoAxiom br -> CoAxiom Branched toBranchedAxiom (CoAxiom unique name role tc branches implicit) @@ -431,7 +427,7 @@ Roles are defined here to avoid circular dependencies. -- See Note [Roles] in Coercion -- defined here to avoid cyclic dependency with Coercion data Role = Nominal | Representational | Phantom - deriving (Eq, Ord, Data.Data, Data.Typeable) + deriving (Eq, Ord, Data.Data) -- These names are slurped into the parser code. Changing these strings -- will change the **surface syntax** that GHC accepts! If you want to @@ -487,7 +483,7 @@ data CoAxiomRule = CoAxiomRule -- the supplied arguments. When this happens in a coercion -- that means that the coercion is ill-formed, and Core Lint -- checks for that. - } deriving Typeable + } instance Data.Data CoAxiomRule where -- don't traverse? diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index 7499e5d505..cc3912d52e 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -2,7 +2,7 @@ (c) The University of Glasgow 2006 -} -{-# LANGUAGE RankNTypes, CPP, DeriveDataTypeable, MultiWayIf #-} +{-# LANGUAGE RankNTypes, CPP, MultiWayIf #-} -- | Module for (a) type kinds and (b) type coercions, -- as used in System FC. See 'CoreSyn.Expr' for diff --git a/compiler/types/InstEnv.hs b/compiler/types/InstEnv.hs index 6b57f5c01e..ec6babc929 100644 --- a/compiler/types/InstEnv.hs +++ b/compiler/types/InstEnv.hs @@ -44,7 +44,7 @@ import BasicTypes import UniqFM import Util import Id -import Data.Data ( Data, Typeable ) +import Data.Data ( Data ) import Data.Maybe ( isJust, isNothing ) {- @@ -76,7 +76,7 @@ data ClsInst -- the decl of BasicTypes.OverlapFlag , is_orphan :: IsOrphan } - deriving (Data, Typeable) + deriving Data -- | A fuzzy comparison function for class instances, intended for sorting -- instances before displaying them to the user. diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index c7a73eab94..7b88519023 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -234,7 +234,7 @@ data Type -- in the list of a TyConApp, when applying a promoted -- GADT data constructor - deriving (Data.Data, Data.Typeable) + deriving Data.Data -- NOTE: Other parts of the code assume that type literals do not contain @@ -242,7 +242,7 @@ data Type data TyLit = NumTyLit Integer | StrTyLit FastString - deriving (Eq, Ord, Data.Data, Data.Typeable) + deriving (Eq, Ord, Data.Data) {- Note [The kind invariant] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -369,14 +369,14 @@ same kinds. data TyBinder = Named TyVar VisibilityFlag -- Always a TyVar (not CoVar or Id) | Anon Type -- Visibility is determined by the type (Constraint vs. *) - deriving (Data.Typeable, Data.Data) + deriving Data.Data -- | Is something required to appear in source Haskell ('Visible'), -- permitted by request ('Specified') (visible type application), or -- prohibited entirely from appearing in source Haskell ('Invisible')? -- See Note [TyBinders and VisibilityFlags] data VisibilityFlag = Visible | Specified | Invisible - deriving (Eq, Data.Typeable, Data.Data) + deriving (Eq, Data.Data) -- | Do these denote the same level of visibility? Except that -- 'Specified' and 'Invisible' are considered the same. Used @@ -820,7 +820,7 @@ data Coercion | SubCo CoercionN -- Turns a ~N into a ~R -- :: N -> R - deriving (Data.Data, Data.Typeable) + deriving Data.Data type CoercionN = Coercion -- always nominal type CoercionR = Coercion -- always representational @@ -830,7 +830,7 @@ type KindCoercion = CoercionN -- always nominal -- If you edit this type, you may need to update the GHC formalism -- See Note [GHC Formalism] in coreSyn/CoreLint.hs data LeftOrRight = CLeft | CRight - deriving( Eq, Data.Data, Data.Typeable ) + deriving( Eq, Data.Data ) instance Binary LeftOrRight where put_ bh CLeft = putByte bh 0 @@ -1193,7 +1193,7 @@ data UnivCoProvenance -- is sound. The string is for the use of the plugin. | HoleProv CoercionHole -- ^ See Note [Coercion holes] - deriving (Data.Data, Data.Typeable) + deriving Data.Data instance Outputable UnivCoProvenance where ppr UnsafeCoerceProv = text "(unsafeCoerce#)" @@ -1207,7 +1207,6 @@ data CoercionHole = CoercionHole { chUnique :: Unique -- ^ used only for debugging , chCoercion :: IORef (Maybe Coercion) } - deriving (Data.Typeable) instance Data.Data CoercionHole where -- don't traverse? diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 55f64166c8..73d898f102 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -6,7 +6,7 @@ The @TyCon@ datatype -} -{-# LANGUAGE CPP, DeriveDataTypeable #-} +{-# LANGUAGE CPP #-} module TyCon( -- * Main TyCon data types @@ -137,7 +137,6 @@ import UniqSet import Module import qualified Data.Data as Data -import Data.Typeable (Typeable) {- ----------------------------------------------- @@ -609,7 +608,6 @@ data TyCon tcTyConScopedTyVars :: [TyVar] -- ^ Scoped tyvars over the -- tycon's body. See Note [TcTyCon] } - deriving Typeable -- | Represents right-hand-sides of 'TyCon's for algebraic types diff --git a/compiler/utils/Bag.hs b/compiler/utils/Bag.hs index 09fddccde1..f2b1ead4d8 100644 --- a/compiler/utils/Bag.hs +++ b/compiler/utils/Bag.hs @@ -6,7 +6,7 @@ Bag: an unordered collection with duplicates -} -{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables, CPP #-} +{-# LANGUAGE ScopedTypeVariables, CPP #-} module Bag ( Bag, -- abstract type @@ -41,7 +41,6 @@ data Bag a | UnitBag a | TwoBags (Bag a) (Bag a) -- INVARIANT: neither branch is empty | ListBag [a] -- INVARIANT: the list is non-empty - deriving Typeable emptyBag :: Bag a emptyBag = EmptyBag diff --git a/compiler/utils/BooleanFormula.hs b/compiler/utils/BooleanFormula.hs index 743b8f11c0..4764b1bfce 100644 --- a/compiler/utils/BooleanFormula.hs +++ b/compiler/utils/BooleanFormula.hs @@ -32,7 +32,7 @@ type LBooleanFormula a = Located (BooleanFormula a) data BooleanFormula a = Var a | And [LBooleanFormula a] | Or [LBooleanFormula a] | Parens (LBooleanFormula a) - deriving (Eq, Data, Typeable, Functor, Foldable, Traversable) + deriving (Eq, Data, Functor, Foldable, Traversable) mkVar :: a -> BooleanFormula a mkVar = Var diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 27bb510299..237c0a23ca 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -1,6 +1,6 @@ -- (c) The University of Glasgow, 1997-2006 -{-# LANGUAGE BangPatterns, CPP, DeriveDataTypeable, MagicHash, UnboxedTuples #-} +{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-} {-# OPTIONS_GHC -O -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised -- compiler is severely affected @@ -175,7 +175,7 @@ data FastString = FastString { n_chars :: {-# UNPACK #-} !Int, -- number of chars fs_bs :: {-# UNPACK #-} !ByteString, fs_ref :: {-# UNPACK #-} !(IORef (Maybe FastZString)) - } deriving Typeable + } instance Eq FastString where f1 == f2 = uniq f1 == uniq f2 diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs index 6c081ea3d0..29854c51fe 100644 --- a/compiler/utils/IOEnv.hs +++ b/compiler/utils/IOEnv.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE CPP #-} -- @@ -39,7 +38,6 @@ import Panic import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef, atomicModifyIORef, atomicModifyIORef' ) -import Data.Typeable import System.IO.Unsafe ( unsafeInterleaveIO ) import System.IO ( fixIO ) import Control.Monad @@ -95,7 +93,6 @@ failWithM :: String -> IOEnv env a failWithM s = IOEnv (\ _ -> ioError (userError s)) data IOEnvFailure = IOEnvFailure - deriving Typeable instance Show IOEnvFailure where show IOEnvFailure = "IOEnv failure" diff --git a/compiler/utils/Panic.hs b/compiler/utils/Panic.hs index b19c770718..721198e211 100644 --- a/compiler/utils/Panic.hs +++ b/compiler/utils/Panic.hs @@ -8,7 +8,7 @@ It's hard to put these functions anywhere else without causing some unnecessary loops in the module dependency graph. -} -{-# LANGUAGE CPP, DeriveDataTypeable, ScopedTypeVariables #-} +{-# LANGUAGE CPP, ScopedTypeVariables #-} module Panic ( GhcException(..), showGhcException, @@ -33,7 +33,6 @@ import Config import Exception import Control.Concurrent -import Data.Dynamic import Debug.Trace ( trace ) import System.IO.Unsafe import System.Environment @@ -86,7 +85,6 @@ data GhcException -- | An error in the user's code, probably. | ProgramError String | PprProgramError String SDoc - deriving (Typeable) instance Exception GhcException diff --git a/compiler/utils/UniqDFM.hs b/compiler/utils/UniqDFM.hs index 91fb0ecbec..d8efde8fe5 100644 --- a/compiler/utils/UniqDFM.hs +++ b/compiler/utils/UniqDFM.hs @@ -60,7 +60,6 @@ import Unique ( Uniquable(..), Unique, getKey ) import Outputable import qualified Data.IntMap as M -import Data.Typeable import Data.Data import Data.List (sortBy) import Data.Function (on) @@ -109,7 +108,7 @@ data TaggedVal val = TaggedVal val {-# UNPACK #-} !Int -- ^ insertion time - deriving (Data, Typeable) + deriving Data taggedFst :: TaggedVal val -> val taggedFst (TaggedVal v _) = v @@ -132,7 +131,7 @@ data UniqDFM ele = -- be distinct within a single map {-# UNPACK #-} !Int -- Upper bound on the values' insertion -- time. See Note [Overflow on plusUDFM] - deriving (Data, Typeable, Functor) + deriving (Data, Functor) emptyUDFM :: UniqDFM elt emptyUDFM = UDFM M.empty 0 diff --git a/libraries/base/Data/Semigroup.hs b/libraries/base/Data/Semigroup.hs index 518e215661..1f4944a411 100644 --- a/libraries/base/Data/Semigroup.hs +++ b/libraries/base/Data/Semigroup.hs @@ -290,7 +290,7 @@ instance Semigroup (NonEmpty a) where newtype Min a = Min { getMin :: a } - deriving (Eq, Ord, Show, Read, Data, Typeable, Generic, Generic1) + deriving (Eq, Ord, Show, Read, Data, Generic, Generic1) instance Bounded a => Bounded (Min a) where minBound = Min minBound @@ -347,7 +347,7 @@ instance Num a => Num (Min a) where fromInteger = Min . fromInteger newtype Max a = Max { getMax :: a } - deriving (Eq, Ord, Show, Read, Data, Typeable, Generic, Generic1) + deriving (Eq, Ord, Show, Read, Data, Generic, Generic1) instance Bounded a => Bounded (Max a) where minBound = Max minBound @@ -405,7 +405,7 @@ instance Num a => Num (Max a) where -- | 'Arg' isn't itself a 'Semigroup' in its own right, but it can be -- placed inside 'Min' and 'Max' to compute an arg min or arg max. data Arg a b = Arg a b deriving - (Show, Read, Data, Typeable, Generic, Generic1) + (Show, Read, Data, Generic, Generic1) type ArgMin a b = Min (Arg a b) type ArgMax a b = Max (Arg a b) @@ -437,7 +437,7 @@ instance Bifunctor Arg where -- | Use @'Option' ('First' a)@ to get the behavior of -- 'Data.Monoid.First' from "Data.Monoid". newtype First a = First { getFirst :: a } deriving - (Eq, Ord, Show, Read, Data, Typeable, Generic, Generic1) + (Eq, Ord, Show, Read, Data, Generic, Generic1) instance Bounded a => Bounded (First a) where minBound = First minBound @@ -482,7 +482,7 @@ instance MonadFix First where -- | Use @'Option' ('Last' a)@ to get the behavior of -- 'Data.Monoid.Last' from "Data.Monoid" newtype Last a = Last { getLast :: a } deriving - (Eq, Ord, Show, Read, Data, Typeable, Generic, Generic1) + (Eq, Ord, Show, Read, Data, Generic, Generic1) instance Bounded a => Bounded (Last a) where minBound = Last minBound @@ -527,7 +527,7 @@ instance MonadFix Last where -- | Provide a Semigroup for an arbitrary Monoid. newtype WrappedMonoid m = WrapMonoid { unwrapMonoid :: m } - deriving (Eq, Ord, Show, Read, Data, Typeable, Generic, Generic1) + deriving (Eq, Ord, Show, Read, Data, Generic, Generic1) instance Monoid m => Semigroup (WrappedMonoid m) where (<>) = coerce (mappend :: m -> m -> m) @@ -570,7 +570,7 @@ mtimesDefault n x -- Ideally, this type would not exist at all and we would just fix the -- 'Monoid' instance of 'Maybe' newtype Option a = Option { getOption :: Maybe a } - deriving (Eq, Ord, Show, Read, Data, Typeable, Generic, Generic1) + deriving (Eq, Ord, Show, Read, Data, Generic, Generic1) instance Functor Option where fmap f (Option a) = Option (fmap f a) diff --git a/libraries/base/GHC/Exception.hs b/libraries/base/GHC/Exception.hs index be9e6f956c..aeaef20805 100644 --- a/libraries/base/GHC/Exception.hs +++ b/libraries/base/GHC/Exception.hs @@ -59,7 +59,7 @@ instance of the @Exception@ class. The simplest case is a new exception type directly below the root: > data MyException = ThisException | ThatException -> deriving (Show, Typeable) +> deriving Show > > instance Exception MyException @@ -79,7 +79,6 @@ of exceptions: > -- Make the root exception type for all the exceptions in a compiler > > data SomeCompilerException = forall e . Exception e => SomeCompilerException e -> deriving Typeable > > instance Show SomeCompilerException where > show (SomeCompilerException e) = show e @@ -98,7 +97,6 @@ of exceptions: > -- Make a subhierarchy for exceptions in the frontend of the compiler > > data SomeFrontendException = forall e . Exception e => SomeFrontendException e -> deriving Typeable > > instance Show SomeFrontendException where > show (SomeFrontendException e) = show e @@ -119,7 +117,7 @@ of exceptions: > -- Make an exception type for a particular frontend compiler exception > > data MismatchedParentheses = MismatchedParentheses -> deriving (Typeable, Show) +> deriving Show > > instance Exception MismatchedParentheses where > toException = frontendExceptionToException diff --git a/libraries/ghci/GHCi/TH.hs b/libraries/ghci/GHCi/TH.hs index 152522166c..69f114cfd2 100644 --- a/libraries/ghci/GHCi/TH.hs +++ b/libraries/ghci/GHCi/TH.hs @@ -42,7 +42,7 @@ runModFinalizers = go =<< getState newtype GHCiQ a = GHCiQ { runGHCiQ :: QState -> IO (a, QState) } data GHCiQException = GHCiQException QState String - deriving (Show, Typeable) + deriving Show instance Exception GHCiQException diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index fc9c80d140..dfcf471f1d 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -790,17 +790,17 @@ dataToPatQ = dataToQa id litP conP ----------------------------------------------------- newtype ModName = ModName String -- Module name - deriving (Show,Eq,Ord,Typeable,Data,Generic) + deriving (Show,Eq,Ord,Data,Generic) newtype PkgName = PkgName String -- package name - deriving (Show,Eq,Ord,Typeable,Data,Generic) + deriving (Show,Eq,Ord,Data,Generic) -- | Obtained from 'reifyModule' and 'thisModule'. data Module = Module PkgName ModName -- package qualified module name - deriving (Show,Eq,Ord,Typeable,Data,Generic) + deriving (Show,Eq,Ord,Data,Generic) newtype OccName = OccName String - deriving (Show,Eq,Ord,Typeable,Data,Generic) + deriving (Show,Eq,Ord,Data,Generic) mkModName :: String -> ModName mkModName s = ModName s @@ -911,7 +911,7 @@ Names constructed using @newName@ and @mkName@ may be used in bindings (such as @let x = ...@ or @\x -> ...@), but names constructed using @lookupValueName@, @lookupTypeName@, @'f@, @''T@ may not. -} -data Name = Name OccName NameFlavour deriving (Typeable, Data, Eq, Generic) +data Name = Name OccName NameFlavour deriving (Data, Eq, Generic) instance Ord Name where -- check if unique is different before looking at strings @@ -927,13 +927,13 @@ data NameFlavour -- An original name (occurrences only, not binders) -- Need the namespace too to be sure which -- thing we are naming - deriving ( Typeable, Data, Eq, Ord, Show, Generic ) + deriving ( Data, Eq, Ord, Show, Generic ) data NameSpace = VarName -- ^ Variables | DataName -- ^ Data constructors | TcClsName -- ^ Type constructors and classes; Haskell has them -- in the same name space for now. - deriving( Eq, Ord, Show, Data, Typeable, Generic ) + deriving( Eq, Ord, Show, Data, Generic ) type Uniq = Int @@ -1184,7 +1184,7 @@ data Loc , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) type CharPos = (Int, Int) -- ^ Line and character position @@ -1261,13 +1261,13 @@ data Info | TyVarI -- Scoped type variable Name Type -- What it is bound to - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | Obtained from 'reifyModule' in the 'Q' Monad. data ModuleInfo = -- | Contains the import list of the module. ModuleInfo [Module] - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) {- | In 'ClassOpI' and 'DataConI', name of the parent class or type @@ -1291,9 +1291,9 @@ type Unlifted = Bool type InstanceDec = Dec data Fixity = Fixity Int FixityDirection - deriving( Eq, Ord, Show, Data, Typeable, Generic ) + deriving( Eq, Ord, Show, Data, Generic ) data FixityDirection = InfixL | InfixR | InfixN - deriving( Eq, Ord, Show, Data, Typeable, Generic ) + deriving( Eq, Ord, Show, Data, Generic ) -- | Highest allowed operator precedence for 'Fixity' constructor (answer: 9) maxPrecedence :: Int @@ -1386,7 +1386,7 @@ data Lit = CharL Char | DoublePrimL Rational | StringPrimL [Word8] -- ^ A primitive C-style string, type Addr# | CharPrimL Char - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- We could add Int, Float, Double etc, as we do in HsLit, -- but that could complicate the @@ -1414,15 +1414,15 @@ data Pat | ListP [ Pat ] -- ^ @{ [1,2,3] }@ | SigP Pat Type -- ^ @{ p :: t }@ | ViewP Exp Pat -- ^ @{ e -> p }@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) type FieldPat = (Name,Pat) data Match = Match Pat Body [Dec] -- ^ @case e of { pat -> body where decs }@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Clause = Clause [Pat] Body [Dec] -- ^ @f { p1 p2 = body where decs }@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Exp = VarE Name -- ^ @{ x }@ @@ -1471,7 +1471,7 @@ data Exp | RecUpdE Exp [FieldExp] -- ^ @{ (f x) { z = w } }@ | StaticE Exp -- ^ @{ static e }@ | UnboundVarE Name -- ^ @{ _x }@ (hole) - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) type FieldExp = (Name,Exp) @@ -1482,23 +1482,23 @@ data Body -- | e3 = e4 } -- where ds@ | NormalB Exp -- ^ @f p { = e } where ds@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Guard = NormalG Exp -- ^ @f x { | odd x } = x@ | PatG [Stmt] -- ^ @f x { | Just y <- x, Just z <- y } = z@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Stmt = BindS Pat Exp | LetS [ Dec ] | NoBindS Exp | ParS [[Stmt]] - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Range = FromR Exp | FromThenR Exp Exp | FromToR Exp Exp | FromThenToR Exp Exp Exp - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Dec = FunD Name [Clause] -- ^ @{ f p1 p2 = b where decs }@ @@ -1565,7 +1565,7 @@ data Dec -- pattern synonyms are supported. See 'PatSynArgs' for details | PatSynSigD Name PatSynType -- ^ A pattern synonym's type signature. - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | Varieties of allowed instance overlap. data Overlap = Overlappable -- ^ May be overlapped by more specific instances @@ -1574,7 +1574,7 @@ data Overlap = Overlappable -- ^ May be overlapped by more specific instances | Incoherent -- ^ Both 'Overlappable' and 'Overlappable', and -- pick an arbitrary one if multiple choices are -- available. - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | A Pattern synonym's type. Note that a pattern synonym's *fully* -- specified type has a peculiar shape coming with two forall @@ -1630,30 +1630,30 @@ type PatSynType = Type -- between @type family@ and @where@. data TypeFamilyHead = TypeFamilyHead Name [TyVarBndr] FamilyResultSig (Maybe InjectivityAnn) - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | One equation of a type family instance or closed type family. The -- arguments are the left-hand-side type patterns and the right-hand-side -- result. data TySynEqn = TySynEqn [Type] Type - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data FunDep = FunDep [Name] [Name] - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data FamFlavour = TypeFam | DataFam - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Foreign = ImportF Callconv Safety String Name Type | ExportF Callconv String Name Type - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- keep Callconv in sync with module ForeignCall in ghc/compiler/prelude/ForeignCall.hs data Callconv = CCall | StdCall | CApi | Prim | JavaScript - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Safety = Unsafe | Safe | Interruptible - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Pragma = InlineP Name Inline RuleMatch Phases | SpecialiseP Name Type (Maybe Inline) Phases @@ -1661,30 +1661,30 @@ data Pragma = InlineP Name Inline RuleMatch Phases | RuleP String [RuleBndr] Exp Exp Phases | AnnP AnnTarget Exp | LineP Int String - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Inline = NoInline | Inline | Inlinable - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) data RuleMatch = ConLike | FunLike - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) data Phases = AllPhases | FromPhase Int | BeforePhase Int - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) data RuleBndr = RuleVar Name | TypedRuleVar Name Type - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) data AnnTarget = ModuleAnnotation | TypeAnnotation Name | ValueAnnotation Name - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) type Cxt = [Pred] -- ^ @(Eq a, Ord b)@ @@ -1697,12 +1697,12 @@ data SourceUnpackedness = NoSourceUnpackedness -- ^ @C a@ | SourceNoUnpack -- ^ @C { {\-\# NOUNPACK \#-\} } a@ | SourceUnpack -- ^ @C { {\-\# UNPACK \#-\} } a@ - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) data SourceStrictness = NoSourceStrictness -- ^ @C a@ | SourceLazy -- ^ @C {~}a@ | SourceStrict -- ^ @C {!}a@ - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) -- | Unlike 'SourceStrictness' and 'SourceUnpackedness', 'DecidedStrictness' -- refers to the strictness that the compiler chooses for a data constructor @@ -1711,7 +1711,7 @@ data SourceStrictness = NoSourceStrictness -- ^ @C a@ data DecidedStrictness = DecidedLazy | DecidedStrict | DecidedUnpack - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) data Con = NormalC Name [BangType] -- ^ @C Int a@ | RecC Name [VarBangType] -- ^ @C { v :: Int, w :: a }@ @@ -1723,7 +1723,7 @@ data Con = NormalC Name [BangType] -- ^ @C Int a@ | RecGadtC [Name] [VarBangType] Type -- See Note [GADT return type] -- ^ @C :: { v :: Int } -> T b Int@ - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) -- Note [GADT return type] -- ~~~~~~~~~~~~~~~~~~~~~~~ @@ -1755,7 +1755,7 @@ data Con = NormalC Name [BangType] -- ^ @C Int a@ data Bang = Bang SourceUnpackedness SourceStrictness -- ^ @C { {\-\# UNPACK \#-\} !}a@ - deriving (Show, Eq, Ord, Data, Typeable, Generic) + deriving (Show, Eq, Ord, Data, Generic) type BangType = (Bang, Type) type VarBangType = (Name, Bang, Type) @@ -1776,14 +1776,14 @@ data PatSynDir = Unidir -- ^ @pattern P x {<-} p@ | ImplBidir -- ^ @pattern P x {=} p@ | ExplBidir [Clause] -- ^ @pattern P x {<-} p where P x = e@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | A pattern synonym's argument type. data PatSynArgs = PrefixPatSyn [Name] -- ^ @pattern P {x y z} = p@ | InfixPatSyn Name Name -- ^ @pattern {x P y} = p@ | RecordPatSyn [Name] -- ^ @pattern P { {x,y,z} } = p@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data Type = ForallT [TyVarBndr] Cxt Type -- ^ @forall \<vars\>. \<ctxt\> -> \<type\>@ | AppT Type Type -- ^ @T a b@ @@ -1810,37 +1810,37 @@ data Type = ForallT [TyVarBndr] Cxt Type -- ^ @forall \<vars\>. \<ctxt\> -> \<t | ConstraintT -- ^ @Constraint@ | LitT TyLit -- ^ @0,1,2, etc.@ | WildCardT -- ^ @_, - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) data TyVarBndr = PlainTV Name -- ^ @a@ | KindedTV Name Kind -- ^ @(a :: k)@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | Type family result signature data FamilyResultSig = NoSig -- ^ no signature | KindSig Kind -- ^ @k@ | TyVarSig TyVarBndr -- ^ @= r, = (r :: k)@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | Injectivity annotation data InjectivityAnn = InjectivityAnn Name [Name] - deriving ( Show, Eq, Ord, Data, Typeable, Generic ) + deriving ( Show, Eq, Ord, Data, Generic ) data TyLit = NumTyLit Integer -- ^ @2@ | StrTyLit String -- ^ @"Hello"@ - deriving ( Show, Eq, Ord, Data, Typeable, Generic ) + deriving ( Show, Eq, Ord, Data, Generic ) -- | Role annotations data Role = NominalR -- ^ @nominal@ | RepresentationalR -- ^ @representational@ | PhantomR -- ^ @phantom@ | InferR -- ^ @_@ - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | Annotation target for reifyAnnotations data AnnLookup = AnnLookupModule Module | AnnLookupName Name - deriving( Show, Eq, Ord, Data, Typeable, Generic ) + deriving( Show, Eq, Ord, Data, Generic ) -- | To avoid duplication between kinds and types, they -- are defined to be the same. Naturally, you would never |