Copyright | (c) 2017 Andrew Lelechenko |
---|---|
License | MIT |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Data.Chimera.Bool
Contents
Description
Semilazy, 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
Chimera
using tabulate
and access this stream via index
instead of recalculation of isOdd
:
isOddBS :: Chimera 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 :: Chimera 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 :: Chimera isPrimeBS = tabulateFix isPrimeF isPrime' :: Word -> Bool isPrime' = index isPrimeBS
Synopsis
- data Chimera
- index :: Chimera -> Word -> Bool
- trueIndices :: Chimera -> [Word]
- falseIndices :: Chimera -> [Word]
- tabulate :: (Word -> Bool) -> Chimera
- tabulateFix :: ((Word -> Bool) -> Word -> Bool) -> Chimera
- tabulateM :: forall m. Monad m => (Word -> m Bool) -> m Chimera
- tabulateFixM :: forall m. Monad m => ((Word -> m Bool) -> Word -> m Bool) -> m Chimera
- mapWithKey :: (Word -> Bool -> Bool) -> Chimera -> Chimera
- traverseWithKey :: forall m. Monad m => (Word -> Bool -> m Bool) -> Chimera -> m Chimera
- not :: Chimera -> Chimera
- zipWithKey :: (Word -> Bool -> Bool -> Bool) -> Chimera -> Chimera -> Chimera
- zipWithKeyM :: forall m. Monad m => (Word -> Bool -> Bool -> m Bool) -> Chimera -> Chimera -> m Chimera
- and :: Chimera -> Chimera -> Chimera
- or :: Chimera -> Chimera -> Chimera
Documentation
Compact representation of an infinite stream of Bool
, offering
indexing via index
in constant time.
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
.
This representation is less lazy than Chimera
:
Querying n-th element triggers computation
of first max(64, 2 ^ ceiling (logBase 2 n))
elements.
index :: Chimera -> 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.
Construction
Manipulation
mapWithKey :: (Word -> Bool -> Bool) -> Chimera -> Chimera Source #
Map over all indices and respective elements in the stream.
traverseWithKey :: forall m. Monad m => (Word -> Bool -> m Bool) -> Chimera -> m Chimera Source #
Traverse over all indices and respective elements in the stream.
zipWithKey :: (Word -> Bool -> Bool -> Bool) -> Chimera -> Chimera -> Chimera Source #
Zip two streams with the function, which is provided with an index and respective elements of both streams.