Copyright | (c) 2018-2019 Andrew Lelechenko |
---|---|
License | MIT |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Data.Chimera
Description
Lazy infinite streams with O(1) indexing.
Synopsis
- memoize :: (Word -> a) -> Word -> a
- memoizeFix :: ((Word -> a) -> Word -> a) -> Word -> a
- data Chimera v a
- type VChimera = Chimera Vector
- type UChimera = Chimera Vector
- tabulate :: Vector v a => (Word -> a) -> Chimera v a
- tabulateFix :: Vector v a => ((Word -> a) -> Word -> a) -> Chimera v a
- iterate :: Vector v a => (a -> a) -> a -> Chimera v a
- cycle :: Vector v a => v a -> Chimera v a
- index :: Vector v a => Chimera v a -> Word -> a
- toList :: Vector v a => Chimera v a -> [a]
- tabulateM :: forall m v a. (Monad m, Vector v a) => (Word -> m a) -> m (Chimera v a)
- tabulateFixM :: forall m v a. (Monad m, Vector v a) => ((Word -> m a) -> Word -> m a) -> m (Chimera v a)
- iterateM :: forall m v a. (Monad m, Vector v a) => (a -> m a) -> a -> m (Chimera v a)
- mapSubvectors :: (Vector u a, Vector v b) => (u a -> v b) -> Chimera u a -> Chimera v b
- zipSubvectors :: (Vector u a, Vector v b, Vector w c) => (u a -> v b -> w c) -> Chimera u a -> Chimera v b -> Chimera w c
Memoization
memoizeFix :: ((Word -> a) -> Word -> a) -> Word -> a Source #
For a given f
memoize a recursive function fix
f
,
caching results in VChimera
.
This is just a shortcut for index
.
tabulateFix
.
memoizeFix f n = fix f n
For example, imagine that we want to memoize Fibonacci numbers:
>>>
fibo n = if n < 2 then fromIntegral n else fibo (n - 1) + fibo (n - 2)
Can we find fiboF
such that fibo
= fix
fiboF
?
Just replace all recursive calls to fibo
with f
:
>>>
fiboF f n = if n < 2 then fromIntegral n else f (n - 1) + f (n - 2)
Now we are ready to use memoizeFix
:
>>>
memoizeFix fiboF 10
55>>>
memoizeFix fiboF 100
354224848179261915075
Chimera
Lazy infinite streams with elements from a
,
backed by a Vector
v
(boxed, unboxed, storable, etc.).
Use tabulate
, tabulateFix
, etc. to create a stream
and index
to access its arbitrary elements
in constant time.
Instances
Functor v => Functor (Chimera v) Source # | |
Applicative (Chimera Vector) Source # |
|
Defined in Data.Chimera Methods pure :: a -> Chimera Vector a # (<*>) :: Chimera Vector (a -> b) -> Chimera Vector a -> Chimera Vector b # liftA2 :: (a -> b -> c) -> Chimera Vector a -> Chimera Vector b -> Chimera Vector c # (*>) :: Chimera Vector a -> Chimera Vector b -> Chimera Vector b # (<*) :: Chimera Vector a -> Chimera Vector b -> Chimera Vector a # | |
Foldable v => Foldable (Chimera v) Source # | |
Defined in Data.Chimera Methods fold :: Monoid m => Chimera v m -> m # foldMap :: Monoid m => (a -> m) -> Chimera v a -> m # foldr :: (a -> b -> b) -> b -> Chimera v a -> b # foldr' :: (a -> b -> b) -> b -> Chimera v a -> b # foldl :: (b -> a -> b) -> b -> Chimera v a -> b # foldl' :: (b -> a -> b) -> b -> Chimera v a -> b # foldr1 :: (a -> a -> a) -> Chimera v a -> a # foldl1 :: (a -> a -> a) -> Chimera v a -> a # toList :: Chimera v a -> [a] # length :: Chimera v a -> Int # elem :: Eq a => a -> Chimera v a -> Bool # maximum :: Ord a => Chimera v a -> a # minimum :: Ord a => Chimera v a -> a # | |
Traversable v => Traversable (Chimera v) Source # | |
Construction
tabulateFix :: Vector v a => ((Word -> a) -> Word -> a) -> Chimera v a Source #
For a given f
create a stream of values of a recursive function fix
f
.
Once created it can be accessed via index
or toList
.
For example, imagine that we want to tabulate Catalan numbers:
>>>
catalan n = if n == 0 then 1 else sum [ catalan i * catalan (n - 1 - i) | i <- [0 .. n - 1] ]
Can we find catalanF
such that catalan
= fix
catalanF
?
Just replace all recursive calls to catalan
with f
:
>>>
catalanF f n = if n == 0 then 1 else sum [ f i * f (n - 1 - i) | i <- [0 .. n - 1] ]
Now we are ready to use tabulateFix
:
>>>
ch = tabulateFix catalanF :: VChimera Integer
>>>
index ch 9
4862>>>
take 10 (toList ch)
[1,1,2,5,14,42,132,429,1430,4862]
iterate :: Vector v a => (a -> a) -> a -> Chimera v a Source #
iterate
f
x
returns an infinite stream
of repeated applications of f
to x
.
>>>
ch = iterate (+ 1) 0 :: UChimera Int
>>>
take 10 (toList ch)
[0,1,2,3,4,5,6,7,8,9]
cycle :: Vector v a => v a -> Chimera v a Source #
Return an infinite repetion of a given vector. Throw an error on an empty vector.
>>>
ch = cycle (Data.Vector.fromList [4, 2]) :: VChimera Int
>>>
take 10 (toList ch)
[4,2,4,2,4,2,4,2,4,2]
Elimination
index :: Vector v a => Chimera v a -> Word -> a Source #
Index a stream in a constant time.
>>>
ch = tabulate (^ 2) :: UChimera Word
>>>
index ch 9
81
toList :: Vector v a => Chimera v a -> [a] Source #
Convert a stream to an infinite list.
>>>
ch = tabulate (^ 2) :: UChimera Word
>>>
take 10 (toList ch)
[0,1,4,9,16,25,36,49,64,81]
Monadic construction
Be careful: the stream is infinite, so monadic effects must be lazy in order to be executed in a finite time.
For instance, lazy state monad works fine:
>>>
import Control.Monad.State.Lazy
>>>
ch = evalState (tabulateM (\i -> do modify (+ i); get)) 0 :: UChimera Word
>>>
take 10 (toList ch)
[0,1,3,6,10,15,21,28,36,45]
But the same computation in the strict state monad Control.Monad.State.Strict diverges.
tabulateM :: forall m v a. (Monad m, Vector v a) => (Word -> m a) -> m (Chimera v a) Source #
Monadic version of tabulate
.
tabulateFixM :: forall m v a. (Monad m, Vector v a) => ((Word -> m a) -> Word -> m a) -> m (Chimera v a) Source #
Monadic version of tabulateFix
.
There are no particular guarantees about the order of recursive calls:
they may be executed more than once or executed in different order.
That said, monadic effects must be idempotent and commutative.
iterateM :: forall m v a. (Monad m, Vector v a) => (a -> m a) -> a -> m (Chimera v a) Source #
Monadic version of iterate
.
Subvectors
Internally Chimera
consists of a number of subvectors.
Following functions provide a low-level access to them.
This ability is especially important for streams of booleans.
Let us use Chimera
to memoize predicates f1
, f2
::
Word
->
Bool
.
Imagine them both already
caught in amber as ch1
, ch2
::
UChimera
Bool
,
and now we want to memoize f3 x = f1 x && f2 x
as ch3
.
One can do it in as follows:
ch3 = tabulate (\i -> index ch1 i && index ch2 i)
There are two unsatisfactory things here. Firstly,
even unboxed vectors store only one boolean per byte.
We would rather reach out for Bit
wrapper,
which provides an instance of unboxed vector
with one boolean per bit. Secondly, combining
existing predicates by indexing them and tabulating again
becomes relatively expensive, given how small and simple
our data is. Fortunately, there is an ultra-fast zipBits
to zip bit vectors. We can combine it altogether like this:
import Data.Bit import Data.Bits ch1 = tabulate (Bit . f1) ch2 = tabulate (Bit . f2) ch3 = zipSubvectors (zipBits (.&.)) ch1 ch2