[commit: packages/base] master: Add `instance {Bits, FiniteBits} Bool` (d679f5e)
git at git.haskell.org
git at git.haskell.org
Sun Nov 24 13:13:12 UTC 2013
Repository : ssh://git@git.haskell.org/base
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/d679f5e9b57935fb0c04ddccb85c69881212979a/base
>---------------------------------------------------------------
commit d679f5e9b57935fb0c04ddccb85c69881212979a
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sun Nov 24 13:14:16 2013 +0100
Add `instance {Bits,FiniteBits} Bool`
This interprets `Bool` as an 1-bit "unsigned" bit-field and provides a
simple (not particularily optimized) implementation to that end.
See "Proposal: Add `instance Bits Bool`" by @ekmett, Nov 2013,
http://permalink.gmane.org/gmane.comp.lang.haskell.libraries/20663
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
d679f5e9b57935fb0c04ddccb85c69881212979a
Data/Bits.hs | 35 +++++++++++++++++++++++++++++++++++
1 file changed, 35 insertions(+)
diff --git a/Data/Bits.hs b/Data/Bits.hs
index 2654a80..f43c8a5 100644
--- a/Data/Bits.hs
+++ b/Data/Bits.hs
@@ -303,6 +303,41 @@ popCountDefault = go 0
go c w = go (c+1) (w .&. (w - 1)) -- clear the least significant
{-# INLINABLE popCountDefault #-}
+
+-- Interpret 'Bool' as 1-bit bit-field; /Since: 4.7.0.0/
+instance Bits Bool where
+ (.&.) = (&&)
+
+ (.|.) = (||)
+
+ xor = (/=)
+
+ complement = not
+
+ shift x 0 = x
+ shift _ _ = False
+
+ rotate x _ = x
+
+ bit 0 = True
+ bit _ = False
+
+ testBit x 0 = x
+ testBit _ _ = False
+
+ bitSizeMaybe _ = Just 1
+
+ bitSize _ = 1
+
+ isSigned _ = False
+
+ popCount False = 0
+ popCount True = 1
+
+instance FiniteBits Bool where
+ finiteBitSize _ = 1
+
+
instance Bits Int where
{-# INLINE shift #-}
{-# INLINE bit #-}
More information about the ghc-commits
mailing list