diff options
Diffstat (limited to 'compiler/simplCore')
-rw-r--r-- | compiler/simplCore/CoreMonad.hs | 5 | ||||
-rw-r--r-- | compiler/simplCore/SimplMonad.hs | 7 |
2 files changed, 5 insertions, 7 deletions
diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs index 3a2277a7a7..29e4b00c4d 100644 --- a/compiler/simplCore/CoreMonad.hs +++ b/compiler/simplCore/CoreMonad.hs @@ -5,6 +5,7 @@ -} {-# LANGUAGE CPP #-} +{-# LANGUAGE DeriveFunctor #-} module CoreMonad ( -- * Configuration of the core-to-core passes @@ -582,9 +583,7 @@ type CoreIOEnv = IOEnv CoreReader -- | The monad used by Core-to-Core passes to access common state, register simplification -- statistics and so on newtype CoreM a = CoreM { unCoreM :: CoreState -> CoreIOEnv (a, CoreState, CoreWriter) } - -instance Functor CoreM where - fmap = liftM + deriving (Functor) instance Monad CoreM where mx >>= f = CoreM $ \s -> do diff --git a/compiler/simplCore/SimplMonad.hs b/compiler/simplCore/SimplMonad.hs index c28f99f9dd..732805e9ee 100644 --- a/compiler/simplCore/SimplMonad.hs +++ b/compiler/simplCore/SimplMonad.hs @@ -4,6 +4,7 @@ \section[SimplMonad]{The simplifier Monad} -} +{-# LANGUAGE DeriveFunctor #-} module SimplMonad ( -- The monad SimplM, @@ -37,7 +38,7 @@ import MonadUtils import ErrUtils as Err import Panic (throwGhcExceptionIO, GhcException (..)) import BasicTypes ( IntWithInf, treatZeroAsInf, mkIntWithInf ) -import Control.Monad ( liftM, ap ) +import Control.Monad ( ap ) {- ************************************************************************ @@ -57,6 +58,7 @@ newtype SimplM result -> SimplCount -> IO (result, UniqSupply, SimplCount)} -- we only need IO here for dump output + deriving (Functor) data SimplTopEnv = STE { st_flags :: DynFlags @@ -104,9 +106,6 @@ computeMaxTicks dflags size {-# INLINE returnSmpl #-} -instance Functor SimplM where - fmap = liftM - instance Applicative SimplM where pure = returnSmpl (<*>) = ap |