bit-stream-0.1.0.2: Lazy, infinite, compact stream of Bool with O(1) indexing.

Copyright(c) 2017 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.BitStream

Description

Lazy, infinite, compact stream of Bool with O(1) indexing. Most useful for memoization of predicates.

Example 1

Consider following predicate:

isOdd :: Word -> Bool
isOdd 0 = False
isOdd n = not (isOdd (n - 1))

Its computation is expensive, so we'd like to memoize its values into BitStream using tabulate and access this stream via index instead of recalculation of isOdd:

isOddBS :: BitStream
isOddBS = tabulate isOdd

isOdd' :: Word -> Bool
isOdd' = index isOddBS

We can do even better by replacing part of recursive calls to isOdd by indexing memoized values. Write isOddF such that isOdd = fix isOddF:

isOddF :: (Word -> Bool) -> Word -> Bool
isOddF _ 0 = False
isOddF f n = not (f (n - 1))

and use tabulateFix:

isOddBS :: BitStream
isOddBS = tabulateFix isOddF

isOdd' :: Word -> Bool
isOdd' = index isOddBS

Example 2

Define a predicate, which checks whether its argument is a prime number by trial division.

isPrime :: Word -> Bool
isPrime n
  | n < 2     = False
  | n < 4     = True
  | even n    = False
  | otherwise = and [ n `rem` d /= 0 | d <- [3, 5 .. ceiling (sqrt (fromIntegral n))], isPrime d]

Convert it to unfixed form:

isPrimeF :: (Word -> Bool) -> Word -> Bool
isPrimeF f n
  | n < 2     = False
  | n < 4     = True
  | even n    = False
  | otherwise = and [ n `rem` d /= 0 | d <- [3, 5 .. ceiling (sqrt (fromIntegral n))], f d]

Create its memoized version for faster evaluation:

isPrimeBS :: BitStream
isPrimeBS = tabulateFix isPrimeF

isPrime' :: Word -> Bool
isPrime' = index isPrimeBS

Synopsis

Documentation

data BitStream Source #

Compact representation of infinite stream of Bool.

It spends one bit (1/8 byte) for one Bool in store. Compare it to at least 24 bytes per element in [Bool], approximately 2 bytes per element in IntSet and 1 byte per element in unboxed Vector Bool.

It also offers indexing in constant time. Compare it to linear time for lists and logarithmic time for sets.

Moreover, it is lazy: querying n-th element triggers computation of first max(64, 2 ^ ceiling (logBase 2 n)) elements only. On contrary, sets and unboxed vectors are completely strict.

tabulate :: (Word -> Bool) -> BitStream Source #

Create a bit stream from the predicate. The predicate must be well-defined for any value of argument and should not return error / undefined.

tabulateFix :: ((Word -> Bool) -> Word -> Bool) -> BitStream Source #

Create a bit stream from the unfixed predicate. The predicate must be well-defined for any value of argument and should not return error / undefined.

tabulateM :: forall m. Monad m => (Word -> m Bool) -> m BitStream Source #

Create a bit stream from the monadic predicate. The predicate must be well-defined for any value of argument and should not return error / undefined.

tabulateFixM :: forall m. Monad m => ((Word -> m Bool) -> Word -> m Bool) -> m BitStream Source #

Create a bit stream from the unfixed monadic predicate. The predicate must be well-defined for any value of argument and should not return error / undefined.

index :: BitStream -> Word -> Bool Source #

Convert a bit stream back to predicate. Indexing itself works in O(1) time, but triggers evaluation and allocation of surrounding elements of the stream, if they were not computed before.

mapWithKey :: (Word -> Bool -> Bool) -> BitStream -> BitStream Source #

Map over all indices and respective elements in the stream.

traverseWithKey :: forall m. Monad m => (Word -> Bool -> m Bool) -> BitStream -> m BitStream Source #

Traverse over all indices and respective elements in the stream.

not :: BitStream -> BitStream Source #

Element-wise not.

zipWithKey :: (Word -> Bool -> Bool -> Bool) -> BitStream -> BitStream -> BitStream Source #

Zip two streams with the function, which is provided with an index and respective elements of both streams.

zipWithKeyM :: forall m. Monad m => (Word -> Bool -> Bool -> m Bool) -> BitStream -> BitStream -> m BitStream Source #

Zip two streams with the monadic function, which is provided with an index and respective elements of both streams.

and :: BitStream -> BitStream -> BitStream Source #

Element-wise and.

or :: BitStream -> BitStream -> BitStream Source #

Element-wise or.