Safe Haskell | None |
---|---|
Language | Haskell2010 |
A bit set based on Enum to name the bits. Use bitwise operations and minimal storage in a safer way.
Similar to Data.Bitset.Generic from bitset package, but
- We don't have the Num constraint
- We dont use the deprecated bitSize function
- We use countTrailingZeros instead of iterating on the number of bits
- We add a typeclass BitOffset
Example:
{--}
data Flag
= FlagXXX
| FlagYYY
| FlagWWW
deriving (Show,Eq,Enum,BitOffset)
-- Adapt the backing type, here we choose Word16
type Flags = BitSet
Word16 Flag
Then you can convert (for free) a Word16 into Flags with fromBits
and
convert back with toBits
.
You can check if a flag is set or not with member
and notMember
and get
a list of set flags with toList
. You can insert
or delete
flags. You
can also perform set operations such as union
and intersection
.
Synopsis
- data BitSet b a
- class BitOffset a where
- toBitOffset :: a -> Word
- fromBitOffset :: Word -> a
- null :: (FiniteBits b, Eq b) => BitSet b a -> Bool
- empty :: FiniteBits b => BitSet b a
- singleton :: (IndexableBits b, BitOffset a) => a -> BitSet b a
- insert :: (IndexableBits b, BitOffset a) => BitSet b a -> a -> BitSet b a
- delete :: (IndexableBits b, BitOffset a) => BitSet b a -> a -> BitSet b a
- toBits :: BitSet b a -> b
- fromBits :: (BitOffset a, FiniteBits b) => b -> BitSet b a
- member :: (BitOffset a, FiniteBits b, IndexableBits b) => BitSet b a -> a -> Bool
- elem :: (BitOffset a, FiniteBits b, IndexableBits b) => a -> BitSet b a -> Bool
- notMember :: (BitOffset a, FiniteBits b, IndexableBits b) => BitSet b a -> a -> Bool
- elems :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b) => BitSet b a -> [a]
- intersection :: (FiniteBits b, Bitwise b) => BitSet b a -> BitSet b a -> BitSet b a
- union :: (FiniteBits b, Bitwise b) => BitSet b a -> BitSet b a -> BitSet b a
- unions :: (FiniteBits b, Bitwise b) => [BitSet b a] -> BitSet b a
- fromListToBits :: (BitOffset a, FiniteBits b, IndexableBits b, Foldable m) => m a -> b
- toListFromBits :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b) => b -> [a]
- enumerateSetBits :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b, Bounded a, Enum a) => b -> [a]
- fromList :: (BitOffset a, IndexableBits b, FiniteBits b, Foldable m) => m a -> BitSet b a
- toList :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b) => BitSet b a -> [a]
Documentation
A bit set: use bitwise operations (fast!) and minimal storage (sizeOf basetype)
- b is the base type (Bits b)
- a is the element type (Enum a)
The elements in the Enum a are flags corresponding to each bit of b starting from the least-significant bit.
Instances
(FiniteBits b, IndexableBits b, BitOffset a, Eq b) => IsList (BitSet b a) Source # | |
Eq b => Eq (BitSet b a) Source # | |
Ord b => Ord (BitSet b a) Source # | |
(Show a, BitOffset a, FiniteBits b, IndexableBits b, Eq b) => Show (BitSet b a) Source # | |
Storable b => Storable (BitSet b a) Source # | |
(FiniteBits b, Integral b, BitOffset a) => Field (BitSet b a) Source # | |
type Item (BitSet b a) Source # | |
Defined in Haskus.Binary.BitSet |
class BitOffset a where Source #
Bit set indexed with a
Nothing
toBitOffset :: a -> Word Source #
Return the bit offset of an element
toBitOffset :: Enum a => a -> Word Source #
Return the bit offset of an element
fromBitOffset :: Word -> a Source #
Return the value associated with a bit offset
fromBitOffset :: Enum a => Word -> a Source #
Return the value associated with a bit offset
Instances
BitOffset Int Source # | It can be useful to get the indexes of the set bits |
Defined in Haskus.Binary.BitSet toBitOffset :: Int -> Word Source # fromBitOffset :: Word -> Int Source # | |
BitOffset Word Source # | It can be useful to get the indexes of the set bits |
Defined in Haskus.Binary.BitSet toBitOffset :: Word -> Word Source # fromBitOffset :: Word -> Word Source # |
empty :: FiniteBits b => BitSet b a Source #
Empty bitset
singleton :: (IndexableBits b, BitOffset a) => a -> BitSet b a Source #
Create a BitSet from a single element
insert :: (IndexableBits b, BitOffset a) => BitSet b a -> a -> BitSet b a Source #
Insert an element in the set
delete :: (IndexableBits b, BitOffset a) => BitSet b a -> a -> BitSet b a Source #
Remove an element from the set
member :: (BitOffset a, FiniteBits b, IndexableBits b) => BitSet b a -> a -> Bool Source #
Test if an element is in the set
elem :: (BitOffset a, FiniteBits b, IndexableBits b) => a -> BitSet b a -> Bool Source #
Test if an element is in the set
notMember :: (BitOffset a, FiniteBits b, IndexableBits b) => BitSet b a -> a -> Bool Source #
Test if an element is not in the set
elems :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b) => BitSet b a -> [a] Source #
Retrieve elements in the set
intersection :: (FiniteBits b, Bitwise b) => BitSet b a -> BitSet b a -> BitSet b a Source #
Intersection of two sets
union :: (FiniteBits b, Bitwise b) => BitSet b a -> BitSet b a -> BitSet b a Source #
Intersection of two sets
unions :: (FiniteBits b, Bitwise b) => [BitSet b a] -> BitSet b a Source #
Intersection of several sets
fromListToBits :: (BitOffset a, FiniteBits b, IndexableBits b, Foldable m) => m a -> b Source #
Convert a list of enum elements into a bitset Warning: b must have enough bits to store the given elements! (we don't perform any check, for performance reason)
toListFromBits :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b) => b -> [a] Source #
Convert a bitset into a list of Enum elements
enumerateSetBits :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b, Bounded a, Enum a) => b -> [a] Source #
Convert a bitset into a list of Enum elements by testing the Enum values successively.
The difference with toListFromBits
is that extra values in the BitSet will
be ignored.
fromList :: (BitOffset a, IndexableBits b, FiniteBits b, Foldable m) => m a -> BitSet b a Source #
Convert a Foldable into a set
toList :: (BitOffset a, FiniteBits b, IndexableBits b, Eq b) => BitSet b a -> [a] Source #
Convert a set into a list