bit-array-0.1.2: 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, FiniteBits 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 and FiniteBits instances from the base type, so it supports all the standard bitwise operations for fixed-size integral types.

Constructors

BitArray a 

Instances

Bounded a => Bounded (BitArray a) Source # 
Enum a => Enum (BitArray a) Source # 
Eq a => Eq (BitArray a) Source # 

Methods

(==) :: BitArray a -> BitArray a -> Bool #

(/=) :: BitArray a -> BitArray a -> Bool #

Integral a => Integral (BitArray a) Source # 
Data a => Data (BitArray a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitArray a -> c (BitArray a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BitArray a) #

toConstr :: BitArray a -> Constr #

dataTypeOf :: BitArray a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (BitArray a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BitArray a)) #

gmapT :: (forall b. Data b => b -> b) -> BitArray a -> BitArray a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitArray a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitArray a -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitArray a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitArray a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitArray a -> m (BitArray a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitArray a -> m (BitArray a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitArray a -> m (BitArray a) #

Num a => Num (BitArray a) Source # 
Ord a => Ord (BitArray a) Source # 

Methods

compare :: BitArray a -> BitArray a -> Ordering #

(<) :: BitArray a -> BitArray a -> Bool #

(<=) :: BitArray a -> BitArray a -> Bool #

(>) :: BitArray a -> BitArray a -> Bool #

(>=) :: BitArray a -> BitArray a -> Bool #

max :: BitArray a -> BitArray a -> BitArray a #

min :: BitArray a -> BitArray a -> BitArray a #

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

Methods

toRational :: BitArray a -> Rational #

FiniteBits a => Show (BitArray a) Source #

Produces a literal of zeros and ones.

>>> show (BitArray (5 :: Int8))
"[qq|00000101|]"

Methods

showsPrec :: Int -> BitArray a -> ShowS #

show :: BitArray a -> String #

showList :: [BitArray a] -> ShowS #

Ix a => Ix (BitArray a) Source # 
FiniteBits a => IsString (BitArray a) Source # 

Methods

fromString :: String -> BitArray a #

Generic (BitArray a) Source # 

Associated Types

type Rep (BitArray a) :: * -> * #

Methods

from :: BitArray a -> Rep (BitArray a) x #

to :: Rep (BitArray a) x -> BitArray a #

Bits a => Bits (BitArray a) Source # 
FiniteBits a => FiniteBits (BitArray a) Source # 
type Rep (BitArray a) Source # 
type Rep (BitArray a) = D1 (MetaData "BitArray" "BitArray" "bit-array-0.1.2-CWQbNqLr0wnDfVii21wplc" True) (C1 (MetaCons "BitArray" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

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 :: FiniteBits a => BitArray a -> String Source #

Convert into a binary notation string.

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

parseString :: FiniteBits 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 :: FiniteBits a => BitArray a -> [a] Source #

Convert into a list of set bits.

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

fromList :: FiniteBits a => [a] -> BitArray a Source #

Construct from a list of set bits.

toBoolList :: FiniteBits 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 :: FiniteBits 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 :: (FiniteBits a, FiniteBits b) => (a -> b) -> BitArray a -> BitArray b Source #

Map over the set bits.

foldr :: FiniteBits a => (a -> b -> b) -> b -> BitArray a -> b Source #

Perform a right-associative fold over the set bits.

mapM_ :: (FiniteBits a, Monad m) => (a -> m b) -> BitArray a -> m () Source #

Traverse thru set bits.

traverse_ :: (FiniteBits a, Applicative f) => (a -> f b) -> BitArray a -> f () Source #

Traverse thru set bits.