summaryrefslogtreecommitdiff
path: root/compiler/hsSyn
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/hsSyn')
-rw-r--r--compiler/hsSyn/Convert.hs7
-rw-r--r--compiler/hsSyn/HsBinds.hs9
2 files changed, 5 insertions, 11 deletions
diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index 2292a9fea4..b4be2f0000 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -6,6 +6,7 @@
This module converts Template Haskell syntax into HsSyn
-}
+{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
@@ -40,7 +41,7 @@ import Outputable
import MonadUtils ( foldrM )
import qualified Data.ByteString as BS
-import Control.Monad( unless, liftM, ap )
+import Control.Monad( unless, ap )
import Data.Maybe( catMaybes, isNothing )
import Language.Haskell.TH as TH hiding (sigP)
@@ -71,6 +72,7 @@ convertToHsType loc t
-------------------------------------------------------------------
newtype CvtM a = CvtM { unCvtM :: SrcSpan -> Either MsgDoc (SrcSpan, a) }
+ deriving (Functor)
-- Push down the source location;
-- Can fail, with a single error message
@@ -83,9 +85,6 @@ newtype CvtM a = CvtM { unCvtM :: SrcSpan -> Either MsgDoc (SrcSpan, a) }
-- In particular, we want it on binding locations, so that variables bound in
-- the spliced-in declarations get a location that at least relates to the splice point
-instance Functor CvtM where
- fmap = liftM
-
instance Applicative CvtM where
pure x = CvtM $ \loc -> Right (loc,x)
(<*>) = ap
diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs
index 8e3448d0f0..1763c3f2de 100644
--- a/compiler/hsSyn/HsBinds.hs
+++ b/compiler/hsSyn/HsBinds.hs
@@ -8,6 +8,7 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind@.
-}
{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
@@ -1262,7 +1263,7 @@ data RecordPatSynField a
, recordPatSynPatVar :: a
-- Filled in by renamer, the name used internally
-- by the pattern
- } deriving Data
+ } deriving (Data, Functor)
@@ -1287,12 +1288,6 @@ when we have a different name for the local and top-level binder
the distinction between the two names clear
-}
-instance Functor RecordPatSynField where
- fmap f (RecordPatSynField { recordPatSynSelectorId = visible
- , recordPatSynPatVar = hidden })
- = RecordPatSynField { recordPatSynSelectorId = f visible
- , recordPatSynPatVar = f hidden }
-
instance Outputable a => Outputable (RecordPatSynField a) where
ppr (RecordPatSynField { recordPatSynSelectorId = v }) = ppr v