[commit: ghc] master: Beautify a few Binary instances (385055c)
Ian Lynagh
igloo at ghc.haskell.org
Sat Jul 27 17:18:49 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/385055c0bdb05743b572b20caec9333a202ef88c
>---------------------------------------------------------------
commit 385055c0bdb05743b572b20caec9333a202ef88c
Author: Ian Lynagh <ian at well-typed.com>
Date: Sat Jul 27 15:47:53 2013 +0100
Beautify a few Binary instances
>---------------------------------------------------------------
compiler/iface/IfaceSyn.lhs | 19 ++++++++++---------
compiler/main/Annotations.hs | 5 +++--
2 files changed, 13 insertions(+), 11 deletions(-)
diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs
index 0150d21..7eb3d3a 100644
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@ -56,6 +56,7 @@ import TysWiredIn ( eqTyConName )
import Fingerprint
import Binary
+import Control.Monad
import System.IO.Unsafe
infixl 3 &&&
@@ -312,10 +313,10 @@ instance Binary IfaceConDecls where
get bh = do
h <- getByte bh
case h of
- 0 -> get bh >>= (return . IfAbstractTyCon)
+ 0 -> liftM IfAbstractTyCon $ get bh
1 -> return IfDataFamTyCon
- 2 -> get bh >>= (return . IfDataTyCon)
- _ -> get bh >>= (return . IfNewTyCon)
+ 2 -> liftM IfDataTyCon $ get bh
+ _ -> liftM IfNewTyCon $ get bh
visibleIfConDecls :: IfaceConDecls -> [IfaceConDecl]
visibleIfConDecls (IfAbstractTyCon {}) = []
@@ -512,7 +513,7 @@ instance Binary IfaceIdInfo where
h <- getByte bh
case h of
0 -> return NoInfo
- _ -> lazyGet bh >>= (return . HasInfo) -- NB lazyGet
+ _ -> liftM HasInfo $ lazyGet bh -- NB lazyGet
-- Here's a tricky case:
-- * Compile with -O module A, and B which imports A.f
@@ -541,12 +542,12 @@ instance Binary IfaceInfoItem where
get bh = do
h <- getByte bh
case h of
- 0 -> get bh >>= (return . HsArity)
- 1 -> get bh >>= (return . HsStrictness)
+ 0 -> liftM HsArity $ get bh
+ 1 -> liftM HsStrictness $ get bh
2 -> do lb <- get bh
ad <- get bh
return (HsUnfold lb ad)
- 3 -> get bh >>= (return . HsInline)
+ 3 -> liftM HsInline $ get bh
_ -> return HsNoCafRefs
-- NB: Specialisations and rules come in separately and are
@@ -777,8 +778,8 @@ instance Binary IfaceConAlt where
h <- getByte bh
case h of
0 -> return IfaceDefault
- 1 -> get bh >>= (return . IfaceDataAlt)
- _ -> get bh >>= (return . IfaceLitAlt)
+ 1 -> liftM IfaceDataAlt $ get bh
+ _ -> liftM IfaceLitAlt $ get bh
data IfaceBinding
= IfaceNonRec IfaceLetBndr IfaceExpr
diff --git a/compiler/main/Annotations.hs b/compiler/main/Annotations.hs
index ec179d8..7de1a99 100644
--- a/compiler/main/Annotations.hs
+++ b/compiler/main/Annotations.hs
@@ -24,6 +24,7 @@ import Serialized
import UniqFM
import Unique
+import Control.Monad
import Data.Maybe
import Data.Typeable
import Data.Word ( Word8 )
@@ -75,8 +76,8 @@ instance Binary name => Binary (AnnTarget name) where
get bh = do
h <- getByte bh
case h of
- 0 -> get bh >>= (return . NamedTarget)
- _ -> get bh >>= (return . ModuleTarget)
+ 0 -> liftM NamedTarget $ get bh
+ _ -> liftM ModuleTarget $ get bh
instance Outputable Annotation where
ppr ann = ppr (ann_target ann)
More information about the ghc-commits
mailing list