diff options
author | Ryan Scott <ryan.gl.scott@gmail.com> | 2016-05-24 09:22:04 -0400 |
---|---|---|
committer | Ryan Scott <ryan.gl.scott@gmail.com> | 2016-05-24 09:22:04 -0400 |
commit | 95dfdceb8b4dcc54a366949577d9ee389bad5bc3 (patch) | |
tree | 02f300a1867a6129f296a66d1e0cb8aefdfde529 /compiler/utils | |
parent | 9d06ef1ae451a145607301dc7556931b537a7d83 (diff) | |
download | haskell-95dfdceb8b4dcc54a366949577d9ee389bad5bc3.tar.gz |
Remove 'deriving Typeable' statements
Summary:
Deriving `Typeable` has been a no-op since GHC 7.10, and now that we
require 7.10+ to build GHC, we can remove all the redundant `deriving Typeable`
statements in GHC.
Test Plan: ./validate
Reviewers: goldfire, austin, hvr, bgamari
Reviewed By: austin, hvr, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2260
Diffstat (limited to 'compiler/utils')
-rw-r--r-- | compiler/utils/Bag.hs | 3 | ||||
-rw-r--r-- | compiler/utils/BooleanFormula.hs | 2 | ||||
-rw-r--r-- | compiler/utils/FastString.hs | 4 | ||||
-rw-r--r-- | compiler/utils/IOEnv.hs | 3 | ||||
-rw-r--r-- | compiler/utils/Panic.hs | 4 | ||||
-rw-r--r-- | compiler/utils/UniqDFM.hs | 5 |
6 files changed, 7 insertions, 14 deletions
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 |