License | BSD-style |
---|---|
Maintainer | Haskell Foundation |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class BitOps bits where
- (.&.) :: bits -> bits -> bits
- (.|.) :: bits -> bits -> bits
- (.^.) :: bits -> bits -> bits
- (.<<.) :: bits -> CountOf Bool -> bits
- (.>>.) :: bits -> CountOf Bool -> bits
- bit :: Offset Bool -> bits
- isBitSet :: bits -> Offset Bool -> Bool
- setBit :: bits -> Offset Bool -> bits
- clearBit :: bits -> Offset Bool -> bits
- class FiniteBitsOps bits where
- data Bits (n :: Nat)
- toBits :: SizeValid n => Natural -> Bits n
- allOne :: forall n. SizeValid n => Bits n
Documentation
class BitOps bits where Source #
operation over bits
(.&.) :: bits -> bits -> bits infixl 7 Source #
(.|.) :: bits -> bits -> bits infixl 5 Source #
(.^.) :: bits -> bits -> bits infixl 6 Source #
(.<<.) :: bits -> CountOf Bool -> bits infixl 8 Source #
(.>>.) :: bits -> CountOf Bool -> bits infixl 8 Source #
bit :: Offset Bool -> bits Source #
construct a bit set with the bit at the given index set.
isBitSet :: bits -> Offset Bool -> Bool Source #
test the bit at the given index is set
setBit :: bits -> Offset Bool -> bits Source #
set the bit at the given index
clearBit :: bits -> Offset Bool -> bits Source #
clear the bit at the given index
Instances
class FiniteBitsOps bits where Source #
operation over finite bits
numberOfBits :: bits -> CountOf Bool Source #
get the number of bits in the given object
rotateL :: bits -> CountOf Bool -> bits infixl 8 Source #
rotate the given bit set.
rotateR :: bits -> CountOf Bool -> bits infixl 8 Source #
rotate the given bit set.
popCount :: bits -> CountOf Bool Source #
count of number of bit set to 1 in the given bit set.
bitFlip :: bits -> bits Source #
reverse all bits in the argument
countLeadingZeros :: bits -> CountOf Bool Source #
count of the number of leading zeros
countTrailingZeros :: bits -> CountOf Bool Source #
count of the number of trailing zeros
Instances
FiniteBitsOps Int16 Source # | |
FiniteBitsOps Int32 Source # | |
FiniteBitsOps Int64 Source # | |
FiniteBitsOps Int8 Source # | |
FiniteBitsOps Word16 Source # | |
Defined in Basement.Bits | |
FiniteBitsOps Word32 Source # | |
Defined in Basement.Bits | |
FiniteBitsOps Word64 Source # | |
Defined in Basement.Bits | |
FiniteBitsOps Word8 Source # | |
FiniteBitsOps Word128 Source # | |
Defined in Basement.Bits | |
FiniteBitsOps Word256 Source # | |
Defined in Basement.Bits | |
FiniteBitsOps Bool Source # | |
FiniteBitsOps Word Source # | |
(SizeValid n, NatWithinBound (CountOf Bool) n) => FiniteBitsOps (Bits n) Source # | |
Defined in Basement.Bits |
Bool set of n
bits.
Instances
SizeValid n => Bounded (Bits n) Source # | |
SizeValid n => Enum (Bits n) Source # | |
Defined in Basement.Bits | |
Show (Bits n) Source # | |
SizeValid n => BitOps (Bits n) Source # | |
Defined in Basement.Bits (.&.) :: Bits n -> Bits n -> Bits n Source # (.|.) :: Bits n -> Bits n -> Bits n Source # (.^.) :: Bits n -> Bits n -> Bits n Source # (.<<.) :: Bits n -> CountOf Bool -> Bits n Source # (.>>.) :: Bits n -> CountOf Bool -> Bits n Source # bit :: Offset Bool -> Bits n Source # isBitSet :: Bits n -> Offset Bool -> Bool Source # | |
(SizeValid n, NatWithinBound (CountOf Bool) n) => FiniteBitsOps (Bits n) Source # | |
Defined in Basement.Bits | |
SizeValid n => Additive (Bits n) Source # | |
SizeValid n => IDivisible (Bits n) Source # | |
SizeValid n => Multiplicative (Bits n) Source # | |
SizeValid n => Subtractive (Bits n) Source # | |
Defined in Basement.Bits type Difference (Bits n) Source # | |
Eq (Bits n) Source # | |
Ord (Bits n) Source # | |
type Difference (Bits n) Source # | |
Defined in Basement.Bits |