haskus-binary-0.6.0.0: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.BitSet

Description

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 CBitSet

Example:

{--}
data Flag
   = FlagXXX
   | FlagYYY
   | FlagWWW
   deriving (Show,Eq,Enum,CBitSet)

-- 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

Documentation

data BitSet b a Source #

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, CBitSet a) => IsList (BitSet b a) Source # 

Associated Types

type Item (BitSet b a) :: * #

Methods

fromList :: [Item (BitSet b a)] -> BitSet b a #

fromListN :: Int -> [Item (BitSet b a)] -> BitSet b a #

toList :: BitSet b a -> [Item (BitSet b a)] #

Eq b => Eq (BitSet b a) Source # 

Methods

(==) :: BitSet b a -> BitSet b a -> Bool #

(/=) :: BitSet b a -> BitSet b a -> Bool #

Ord b => Ord (BitSet b a) Source # 

Methods

compare :: BitSet b a -> BitSet b a -> Ordering #

(<) :: BitSet b a -> BitSet b a -> Bool #

(<=) :: BitSet b a -> BitSet b a -> Bool #

(>) :: BitSet b a -> BitSet b a -> Bool #

(>=) :: BitSet b a -> BitSet b a -> Bool #

max :: BitSet b a -> BitSet b a -> BitSet b a #

min :: BitSet b a -> BitSet b a -> BitSet b a #

(Show a, CBitSet a, FiniteBits b) => Show (BitSet b a) Source # 

Methods

showsPrec :: Int -> BitSet b a -> ShowS #

show :: BitSet b a -> String #

showList :: [BitSet b a] -> ShowS #

Storable b => Storable (BitSet b a) Source # 

Methods

peekIO :: Ptr (BitSet b a) -> IO (BitSet b a) Source #

pokeIO :: Ptr (BitSet b a) -> BitSet b a -> IO () Source #

alignment :: BitSet b a -> Word Source #

sizeOf :: BitSet b a -> Word Source #

(FiniteBits b, Integral b, CBitSet a) => Field (BitSet b a) Source # 

Methods

fromField :: Integral b => BitSet b a -> b

toField :: Integral b => b -> BitSet b a

type Item (BitSet b a) Source # 
type Item (BitSet b a) = a

class CBitSet a where Source #

Bit set indexed with a

Methods

toBitOffset :: a -> Int Source #

Return the bit offset of an element

toBitOffset :: Enum a => a -> Int Source #

Return the bit offset of an element

fromBitOffset :: Int -> a Source #

Return the value associated with a bit offset

fromBitOffset :: Enum a => Int -> a Source #

Return the value associated with a bit offset

Instances

CBitSet Int Source #

It can be useful to get the indexes of the set bits

null :: FiniteBits b => BitSet b a -> Bool Source #

Indicate if the set is empty

empty :: FiniteBits b => BitSet b a Source #

Empty bitset

singleton :: (Bits b, CBitSet a) => a -> BitSet b a Source #

Create a BitSet from a single element

insert :: (Bits b, CBitSet a) => BitSet b a -> a -> BitSet b a Source #

Insert an element in the set

delete :: (Bits b, CBitSet a) => BitSet b a -> a -> BitSet b a Source #

Remove an element from the set

toBits :: BitSet b a -> b Source #

Unwrap the bitset

fromBits :: (CBitSet a, FiniteBits b) => b -> BitSet b a Source #

Wrap a bitset

member :: (CBitSet a, FiniteBits b) => BitSet b a -> a -> Bool Source #

Test if an element is in the set

elem :: (CBitSet a, FiniteBits b) => a -> BitSet b a -> Bool Source #

Test if an element is in the set

notMember :: (CBitSet a, FiniteBits b) => BitSet b a -> a -> Bool Source #

Test if an element is not in the set

elems :: (CBitSet a, FiniteBits b) => BitSet b a -> [a] Source #

Retrieve elements in the set

intersection :: FiniteBits b => BitSet b a -> BitSet b a -> BitSet b a Source #

Intersection of two sets

union :: FiniteBits b => BitSet b a -> BitSet b a -> BitSet b a Source #

Intersection of two sets

unions :: FiniteBits b => [BitSet b a] -> BitSet b a Source #

Intersection of several sets

fromListToBits :: (CBitSet a, FiniteBits 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 :: (CBitSet a, FiniteBits b) => b -> [a] Source #

Convert a bitset into a list of Enum elements

fromList :: (CBitSet a, FiniteBits b, Foldable m) => m a -> BitSet b a Source #

Convert a Foldable into a set

toList :: (CBitSet a, FiniteBits b) => BitSet b a -> [a] Source #

Convert a set into a list