bit-array-0.1.0.1: A bit array (aka bitset, bitmap, bit vector) API for numeric types

Safe HaskellNone
LanguageHaskell2010

BitArray

Contents

Synopsis

Documentation

newtype BitArray a Source

A newtype wrapper which provides an array-like interface to a type, which has instances of Bits and Num.

You can construct bit arrays by wrapping numeric values:

>>> BitArray (7 :: Int8)
[qq|00000111|]

or directly from numeric literals:

>>> 7 :: BitArray Int8
[qq|00000111|]

or using a binary notation quasi-quoter, assuming you have the QuasiQuotes pragma turned on:

>>> [qq|0111|] :: BitArray Int8
[qq|00000111|]

BitArray derives the Bits instance from the base type, so it supports all the standard bitwise operations as well.

Note that this library does not support the Integer type, since Integer has no implementation of the bitSize function, which this library heavily relies on. You will get a runtime exception if you use it with Integer.

Constructors

BitArray a 

Instances

Bounded a => Bounded (BitArray a) Source 
Enum a => Enum (BitArray a) Source 
Eq a => Eq (BitArray a) Source 
Integral a => Integral (BitArray a) Source 
Data a => Data (BitArray a) Source 
Num a => Num (BitArray a) Source 
Ord a => Ord (BitArray a) Source 
(Bits a, Num a) => Read (BitArray a) Source

Parses a literal of zeros and ones.

>>> read "[qq|1110|]" :: BitArray Int8
[qq|00001110|]
>>> unwrap (read "[qq|1110|]") :: Int
14
Real a => Real (BitArray a) Source 
Bits a => Show (BitArray a) Source

Produces a literal of zeros and ones.

>>> show (BitArray (5 :: Int8))
"[qq|00000101|]"
Ix a => Ix (BitArray a) Source 
(Bits a, Num a) => IsString (BitArray a) Source 
Generic (BitArray a) Source 
Bits a => Bits (BitArray a) Source 
type Rep (BitArray a) Source 

Constructors and converters

qq :: QuasiQuoter Source

A binary number quasi-quoter. Produces a numeric literal at compile time. Can be used to construct both bit arrays and integral numbers.

>>> [qq|011|] :: Int
3
>>> [qq|011|] :: BitArray Int8
[qq|00000011|]

unwrap :: BitArray a -> a Source

Unwrap the underlying value of a bit array.

Strings

toString :: Bits a => BitArray a -> String Source

Convert into a binary notation string.

>>> toString (BitArray (5 :: Int8))
"00000101"

parseString :: (Bits a, Num a) => String -> Maybe (BitArray a) Source

Parse a binary notation string.

>>> parseString "123" :: Maybe (BitArray Int8)
Nothing
>>> parseString "101" :: Maybe (BitArray Int8)
Just [qq|00000101|]

Lists

toList :: (Bits a, Num a) => BitArray a -> [a] Source

Convert into a list of set bits.

The list is ordered from least significant to most significant bit.

fromList :: (Bits a, Num a) => [a] -> BitArray a Source

Construct from a list of set bits.

toBoolList :: Bits a => BitArray a -> [Bool] Source

Convert into a list of boolean values, which represent the "set" flags of each bit.

The list is ordered from least significant to most significant bit.

fromBoolList :: (Bits a, Num a) => [Bool] -> BitArray a Source

Construct from a list of boolean flags for the "set" status of each bit.

The list must be ordered from least significant to most significant bit.

Utils

map :: (Bits a, Num a, Bits b, Num b) => (a -> b) -> BitArray a -> BitArray b Source

Map over the set bits.

foldr :: (Bits a, Num a) => (a -> b -> b) -> b -> BitArray a -> b Source

Perform a right-associative fold over the set bits.

mapM_ :: (Bits a, Num a, Monad m) => (a -> m b) -> BitArray a -> m () Source

Traverse thru set bits.

traverse_ :: (Bits a, Num a, Applicative f) => (a -> f b) -> BitArray a -> f () Source

Traverse thru set bits.