summaryrefslogtreecommitdiff
path: root/compiler/cmm
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/cmm')
-rw-r--r--compiler/cmm/CmmLint.hs7
-rw-r--r--compiler/cmm/Hoopl/Block.hs12
-rw-r--r--compiler/cmm/PprC.hs9
3 files changed, 10 insertions, 18 deletions
diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs
index 3224bb8cab..d5c3f84443 100644
--- a/compiler/cmm/CmmLint.hs
+++ b/compiler/cmm/CmmLint.hs
@@ -5,6 +5,7 @@
-- CmmLint: checking the correctness of Cmm statements and expressions
--
-----------------------------------------------------------------------------
+{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GADTs #-}
module CmmLint (
cmmLint, cmmLintGraph
@@ -24,7 +25,7 @@ import PprCmm ()
import Outputable
import DynFlags
-import Control.Monad (liftM, ap)
+import Control.Monad (ap)
-- Things to check:
-- - invariant on CmmBlock in CmmExpr (see comment there)
@@ -212,9 +213,7 @@ checkCond _ expr
-- just a basic error monad:
newtype CmmLint a = CmmLint { unCL :: DynFlags -> Either SDoc a }
-
-instance Functor CmmLint where
- fmap = liftM
+ deriving (Functor)
instance Applicative CmmLint where
pure a = CmmLint (\_ -> Right a)
diff --git a/compiler/cmm/Hoopl/Block.hs b/compiler/cmm/Hoopl/Block.hs
index c4ff1794e8..5c31932934 100644
--- a/compiler/cmm/Hoopl/Block.hs
+++ b/compiler/cmm/Hoopl/Block.hs
@@ -1,7 +1,9 @@
+{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE StandaloneDeriving #-}
module Hoopl.Block
( C
, O
@@ -64,14 +66,8 @@ data MaybeC ex t where
JustC :: t -> MaybeC C t
NothingC :: MaybeC O t
-
-instance Functor (MaybeO ex) where
- fmap _ NothingO = NothingO
- fmap f (JustO a) = JustO (f a)
-
-instance Functor (MaybeC ex) where
- fmap _ NothingC = NothingC
- fmap f (JustC a) = JustC (f a)
+deriving instance Functor (MaybeO ex)
+deriving instance Functor (MaybeC ex)
-- -----------------------------------------------------------------------------
-- The Block type
diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs
index 822de431a4..2038801de3 100644
--- a/compiler/cmm/PprC.hs
+++ b/compiler/cmm/PprC.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, GADTs #-}
+{-# LANGUAGE CPP, DeriveFunctor, GADTs, PatternSynonyms #-}
-----------------------------------------------------------------------------
--
@@ -61,7 +61,7 @@ import Data.Map (Map)
import Data.Word
import System.IO
import qualified Data.Map as Map
-import Control.Monad (liftM, ap)
+import Control.Monad (ap)
import qualified Data.Array.Unsafe as U ( castSTUArray )
import Data.Array.ST
@@ -1078,10 +1078,7 @@ pprExternDecl lbl
<> semi
type TEState = (UniqSet LocalReg, Map CLabel ())
-newtype TE a = TE { unTE :: TEState -> (a, TEState) }
-
-instance Functor TE where
- fmap = liftM
+newtype TE a = TE { unTE :: TEState -> (a, TEState) } deriving (Functor)
instance Applicative TE where
pure a = TE $ \s -> (a, s)