[GHC] #15993: Bitwise-oriented semigroup and monoid newtype wrappers for Data.Bits.Bits instances

#15993: Bitwise-oriented semigroup and monoid newtype wrappers for Data.Bits.Bits instances -------------------------------------+------------------------------------- Reporter: koz_ | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.6.3 Component: | Version: 8.6.2 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I've found myself needing these often, and given the existence of similar newtypes for directing `(<>)` and `mempty` for a range of other types, these are conspicuous by their absence. Additionally, while `oneBits` isn't technically necessary, it's a lot more concise than `complement zeroBits`, and I found myself needing it often. To that end, I've sketched up this implementation. Technically speaking, GND isn't needed, but it means I don't have to repeat myself a lot. These could be made even more concise with `coerce`, but I decided not to do that, since that would require `TypeApplications`. I've limited derivation to methods that are specifically about bitwise operations, rather than stuff like `Num`. {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Data.Bits.Extra where import Data.Bits ( Bits(..) , FiniteBits(..) ) -- | Monoid under bitwise AND. newtype Conj a = Conj { getConj :: a } deriving (Eq, Bounded, Enum, Bits, FiniteBits) instance (Bits a) => Semigroup (Conj a) where (Conj x) <> (Conj y) = Conj (x .&. y) instance (Bits a) => Monoid (Conj a) where mempty = Conj . complement $ zeroBits -- | Monoid under bitwise OR. newtype Disj a = Disj { getDisj :: a } deriving (Eq, Bounded, Enum, Bits, FiniteBits) instance (Bits a) => Semigroup (Disj a) where (Disj x) <> (Disj y) = Disj (x .|. y) instance (Bits a) => Monoid (Disj a) where mempty = Disj zeroBits -- | Semigroup under bitwise XOR. newtype Xor a = Xor { getXor :: a } deriving (Eq, Bounded, Enum, Bits, FiniteBits) instance (Bits a) => Semigroup (Xor a) where (Xor x) <> (Xor y) = Xor (x `xor` y) -- | Semigroup under bitwise \'equality\'; defined as '1' if the corresponding -- bits match, '0' otherwise. newtype Iff a = Iff { getIff :: a } deriving (Eq, Bounded, Enum, Bits, FiniteBits) instance (Bits a) => Semigroup (Iff a) where (Iff x) <> (Iff y) = Iff . complement $ (x `xor` y) -- not strictly necessary, but would be a big help -- probably should be INLINE oneBits :: (Bits a) => a oneBits = complement zeroBits }}} Potentially this could include more, such as instances of `Ord` based on lexicographic ordering on the bits, rather than defaulting to the underlying one (such as the one for `Int`, which I believe is numeric). However, that's a separate issue. I also don't know if these belong in `Data.Bits` or `Data.Semigroup` (or `Data.Monoid` I guess). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15993 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC