diff options
Diffstat (limited to 'compiler/nativeGen')
-rw-r--r-- | compiler/nativeGen/AsmCodeGen.hs | 9 | ||||
-rw-r--r-- | compiler/nativeGen/NCGMonad.hs | 7 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Linear/State.hs | 9 |
3 files changed, 11 insertions, 14 deletions
diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index cc608b1ec6..ed0c57e1e2 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -6,7 +6,8 @@ -- -- ----------------------------------------------------------------------------- -{-# LANGUAGE BangPatterns, CPP, GADTs, ScopedTypeVariables, PatternSynonyms #-} +{-# LANGUAGE BangPatterns, CPP, GADTs, ScopedTypeVariables, PatternSynonyms, + DeriveFunctor #-} #if !defined(GHC_LOADED_INTO_GHCI) {-# LANGUAGE UnboxedTuples #-} @@ -1038,13 +1039,11 @@ pattern OptMResult x y = (# x, y #) {-# COMPLETE OptMResult #-} #else -data OptMResult a = OptMResult !a ![CLabel] +data OptMResult a = OptMResult !a ![CLabel] deriving (Functor) #endif newtype CmmOptM a = CmmOptM (DynFlags -> Module -> [CLabel] -> OptMResult a) - -instance Functor CmmOptM where - fmap = liftM + deriving (Functor) instance Applicative CmmOptM where pure x = CmmOptM $ \_ _ imports -> OptMResult x imports diff --git a/compiler/nativeGen/NCGMonad.hs b/compiler/nativeGen/NCGMonad.hs index 0f53ef6690..3680c1c7b0 100644 --- a/compiler/nativeGen/NCGMonad.hs +++ b/compiler/nativeGen/NCGMonad.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE DeriveFunctor #-} -- ----------------------------------------------------------------------------- -- @@ -59,7 +60,7 @@ import Unique ( Unique ) import DynFlags import Module -import Control.Monad ( liftM, ap ) +import Control.Monad ( ap ) import Instruction import Outputable (SDoc, pprPanic, ppr) @@ -113,6 +114,7 @@ data NatM_State type DwarfFiles = UniqFM (FastString, Int) newtype NatM result = NatM (NatM_State -> (result, NatM_State)) + deriving (Functor) unNat :: NatM a -> NatM_State -> (a, NatM_State) unNat (NatM a) = a @@ -138,9 +140,6 @@ initNat :: NatM_State -> NatM a -> (a, NatM_State) initNat init_st m = case unNat m init_st of { (r,st) -> (r,st) } -instance Functor NatM where - fmap = liftM - instance Applicative NatM where pure = returnNat (<*>) = ap diff --git a/compiler/nativeGen/RegAlloc/Linear/State.hs b/compiler/nativeGen/RegAlloc/Linear/State.hs index 8df4dd04f0..43b8f6c129 100644 --- a/compiler/nativeGen/RegAlloc/Linear/State.hs +++ b/compiler/nativeGen/RegAlloc/Linear/State.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, PatternSynonyms #-} +{-# LANGUAGE CPP, PatternSynonyms, DeriveFunctor #-} #if !defined(GHC_LOADED_INTO_GHCI) {-# LANGUAGE UnboxedTuples #-} @@ -50,7 +50,7 @@ import DynFlags import Unique import UniqSupply -import Control.Monad (liftM, ap) +import Control.Monad (ap) -- Avoids using unboxed tuples when loading into GHCi #if !defined(GHC_LOADED_INTO_GHCI) @@ -63,15 +63,14 @@ pattern RA_Result a b = (# a, b #) #else data RA_Result freeRegs a = RA_Result {-# UNPACK #-} !(RA_State freeRegs) !a + deriving (Functor) #endif -- | The register allocator monad type. newtype RegM freeRegs a = RegM { unReg :: RA_State freeRegs -> RA_Result freeRegs a } - -instance Functor (RegM freeRegs) where - fmap = liftM + deriving (Functor) instance Applicative (RegM freeRegs) where pure a = RegM $ \s -> RA_Result s a |