{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Monoid.BitAnd where
import Data.Bits
import Data.Coerce (coerce)
import qualified Data.Foldable as F
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Generic.Mutable as GM
import qualified Data.Vector.Unboxed as U
newtype BitAnd a = BitAnd {forall a. BitAnd a -> a
getBitAnd :: a}
deriving (BitAnd a -> BitAnd a -> Bool
(BitAnd a -> BitAnd a -> Bool)
-> (BitAnd a -> BitAnd a -> Bool) -> Eq (BitAnd a)
forall a. Eq a => BitAnd a -> BitAnd a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => BitAnd a -> BitAnd a -> Bool
== :: BitAnd a -> BitAnd a -> Bool
$c/= :: forall a. Eq a => BitAnd a -> BitAnd a -> Bool
/= :: BitAnd a -> BitAnd a -> Bool
Eq, Int -> BitAnd a -> ShowS
[BitAnd a] -> ShowS
BitAnd a -> String
(Int -> BitAnd a -> ShowS)
-> (BitAnd a -> String) -> ([BitAnd a] -> ShowS) -> Show (BitAnd a)
forall a. Show a => Int -> BitAnd a -> ShowS
forall a. Show a => [BitAnd a] -> ShowS
forall a. Show a => BitAnd a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> BitAnd a -> ShowS
showsPrec :: Int -> BitAnd a -> ShowS
$cshow :: forall a. Show a => BitAnd a -> String
show :: BitAnd a -> String
$cshowList :: forall a. Show a => [BitAnd a] -> ShowS
showList :: [BitAnd a] -> ShowS
Show)
instance (Bits a) => Semigroup (BitAnd a) where
<> :: BitAnd a -> BitAnd a -> BitAnd a
(<>) = (a -> a -> a) -> BitAnd a -> BitAnd a -> BitAnd a
forall a b. Coercible a b => a -> b
coerce (forall a. Bits a => a -> a -> a
(.&.) @a)
{-# INLINE (<>) #-}
instance (Bits a) => Monoid (BitAnd a) where
mempty :: BitAnd a
mempty = a -> BitAnd a
forall a b. Coercible a b => a -> b
coerce (a -> BitAnd a) -> a -> BitAnd a
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Bits a => a -> a
complement (forall a. Bits a => a
zeroBits @a)
{-# INLINE mempty #-}
mconcat :: [BitAnd a] -> BitAnd a
mconcat = (BitAnd a -> BitAnd a -> BitAnd a)
-> BitAnd a -> [BitAnd a] -> BitAnd a
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' BitAnd a -> BitAnd a -> BitAnd a
forall a. Monoid a => a -> a -> a
mappend BitAnd a
forall a. Monoid a => a
mempty
{-# INLINE mconcat #-}
newtype instance U.MVector s (BitAnd a) = MV_BitAnd (U.MVector s a)
newtype instance U.Vector (BitAnd a) = V_BitAnd (U.Vector a)
deriving newtype instance (U.Unbox a) => GM.MVector U.MVector (BitAnd a)
deriving newtype instance (U.Unbox a) => G.Vector U.Vector (BitAnd a)
instance (U.Unbox a) => U.Unbox (BitAnd a)