chimera-0.3.3.0: Lazy infinite streams with O(1) indexing and applications for memoization
Copyright(c) 2018-2019 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Chimera

Description

Lazy infinite streams with O(1) indexing.

Synopsis

Memoization

memoize :: (Word -> a) -> Word -> a Source #

Memoize a function: repeating calls to memoize f n would compute f n only once and cache the result in VChimera. This is just a shortcut for index . tabulate. When a is Unbox, it is faster to use index (tabulate f :: UChimera a).

memoize f n = f n

Since: 0.3.0.0

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. When a is Unbox, it is faster to use index (tabulateFix f :: UChimera a).

memoizeFix f n = fix f n

For example, imagine that we want to memoize Fibonacci numbers:

>>> fibo n = if n < 2 then toInteger 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 toInteger n else f (n - 1) + f (n - 2)

Now we are ready to use memoizeFix:

>>> memoizeFix fiboF 10
55
>>> memoizeFix fiboF 100
354224848179261915075

This function can be used even when arguments of recursive calls are not strictly decreasing, but they might not get memoized. If this is not desired use tabulateFix' instead. For example, here is a routine to measure the length of Collatz sequence:

>>> collatzF f n = if n <= 1 then 0 else 1 + f (if even n then n `quot` 2 else 3 * n + 1)
>>> memoizeFix collatzF 27
111

Since: 0.3.0.0

Chimera

data Chimera v a Source #

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.

Since: 0.2.0.0

Instances

Instances details
MonadReader Word (Chimera Vector) Source #

Since: 0.3.1.0

Instance details

Defined in Data.Chimera

Methods

ask :: Chimera Vector Word #

local :: (Word -> Word) -> Chimera Vector a -> Chimera Vector a #

reader :: (Word -> a) -> Chimera Vector a #

Representable (Chimera Vector) Source #

Since: 0.3.1.0

Instance details

Defined in Data.Chimera

Associated Types

type Rep (Chimera Vector) #

Methods

tabulate :: (Rep (Chimera Vector) -> a) -> Chimera Vector a #

index :: Chimera Vector a -> Rep (Chimera Vector) -> a #

MonadFix (Chimera Vector) Source #

Since: 0.3.1.0

Instance details

Defined in Data.Chimera

Methods

mfix :: (a -> Chimera Vector a) -> Chimera Vector a #

MonadZip (Chimera Vector) Source #

Since: 0.3.1.0

Instance details

Defined in Data.Chimera

Methods

mzip :: Chimera Vector a -> Chimera Vector b -> Chimera Vector (a, b) #

mzipWith :: (a -> b -> c) -> Chimera Vector a -> Chimera Vector b -> Chimera Vector c #

munzip :: Chimera Vector (a, b) -> (Chimera Vector a, Chimera Vector b) #

Foldable v => Foldable (Chimera v) Source #

Since: 0.2.0.0

Instance details

Defined in Data.Chimera

Methods

fold :: Monoid m => Chimera v m -> m #

foldMap :: Monoid m => (a -> m) -> Chimera v a -> 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] #

null :: Chimera v a -> Bool #

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 #

sum :: Num a => Chimera v a -> a #

product :: Num a => Chimera v a -> a #

Traversable v => Traversable (Chimera v) Source #

Since: 0.2.0.0

Instance details

Defined in Data.Chimera

Methods

traverse :: Applicative f => (a -> f b) -> Chimera v a -> f (Chimera v b) #

sequenceA :: Applicative f => Chimera v (f a) -> f (Chimera v a) #

mapM :: Monad m => (a -> m b) -> Chimera v a -> m (Chimera v b) #

sequence :: Monad m => Chimera v (m a) -> m (Chimera v a) #

Applicative (Chimera Vector) Source #

pure creates a constant stream.

Since: 0.2.0.0

Instance details

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 #

Functor v => Functor (Chimera v) Source #

Since: 0.2.0.0

Instance details

Defined in Data.Chimera

Methods

fmap :: (a -> b) -> Chimera v a -> Chimera v b #

(<$) :: a -> Chimera v b -> Chimera v a #

Monad (Chimera Vector) Source #

Since: 0.3.1.0

Instance details

Defined in Data.Chimera

Distributive (Chimera Vector) Source #

Since: 0.3.1.0

Instance details

Defined in Data.Chimera

Methods

distribute :: Functor f => f (Chimera Vector a) -> Chimera Vector (f a) #

collect :: Functor f => (a -> Chimera Vector b) -> f a -> Chimera Vector (f b) #

distributeM :: Monad m => m (Chimera Vector a) -> Chimera Vector (m a) #

collectM :: Monad m => (a -> Chimera Vector b) -> m a -> Chimera Vector (m b) #

type Rep (Chimera Vector) Source # 
Instance details

Defined in Data.Chimera

type VChimera = Chimera Vector Source #

Streams backed by boxed vectors.

Since: 0.3.0.0

type UChimera = Chimera Vector Source #

Streams backed by unboxed vectors.

Since: 0.3.0.0

Construction

tabulate :: Vector v a => (Word -> a) -> Chimera v a Source #

Create a stream of values of a given function. Once created it can be accessed via index or toList.

>>> ch = tabulate (^ 2) :: UChimera Word
>>> index ch 9
81
>>> take 10 (toList ch)
[0,1,4,9,16,25,36,49,64,81]

Since: 0.2.0.0

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]

Note: Only recursive function calls with decreasing arguments are memoized. If full memoization is desired, use tabulateFix' instead.

Since: 0.2.0.0

tabulateFix' :: Vector v a => ((Word -> a) -> Word -> a) -> Chimera v a Source #

Fully memoizing version of tabulateFix. This function will tabulate every recursive call, but might allocate a lot of memory in doing so. For example, the following piece of code calculates the highest number reached by the Collatz sequence of a given number, but also allocates tens of gigabytes of memory, because the Collatz sequence will spike to very high numbers.

>>> collatzF :: (Word -> Word) -> (Word -> Word)
>>> collatzF _ 0 = 0
>>> collatzF f n = if n <= 2 then 4 else n `max` f (if even n then n `quot` 2 else 3 * n + 1)
>>> 
>>> maximumBy (comparing $ index $ tabulateFix' collatzF) [0..1000000]
...

Using memoizeFix instead fixes the problem:

>>> maximumBy (comparing $ memoizeFix collatzF) [0..1000000]
56991483520

Since: 0.3.2.0

iterate :: Vector v a => (a -> a) -> a -> Chimera v a Source #

iterate f x returns an infinite stream, generated by 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]

Since: 0.3.0.0

unfoldr :: Vector v b => (a -> (b, a)) -> a -> Chimera v b Source #

unfoldr f x returns an infinite stream, generated by repeated applications of f to x, similar to unfoldr.

>>> ch = unfoldr (\acc -> (acc * acc, acc + 1)) 0 :: UChimera Int
>>> take 10 (toList ch)
[0,1,4,9,16,25,36,49,64,81]

Since: 0.3.3.0

cycle :: Vector v a => v a -> Chimera v a Source #

Return an infinite repetition 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]

Since: 0.3.0.0

fromListWithDef Source #

Arguments

:: Vector v a 
=> a

Default value

-> [a]

Prefix

-> Chimera v a 

Create a stream of values from a given prefix, followed by default value afterwards.

Since: 0.3.3.0

fromVectorWithDef Source #

Arguments

:: Vector v a 
=> a

Default value

-> v a

Prefix

-> Chimera v a 

Create a stream of values from a given prefix, followed by default value afterwards.

Since: 0.3.3.0

Manipulation

interleave :: Vector v a => Chimera v a -> Chimera v a -> Chimera v a Source #

Intertleave two streams, sourcing even elements from the first one and odd elements from the second one.

>>> ch = interleave (tabulate id) (tabulate (+ 100)) :: UChimera Word
>>> take 10 (toList ch)
[0,100,1,101,2,102,3,103,4,104]

Since: 0.3.3.0

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

Since: 0.2.0.0

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]

Since: 0.3.0.0

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 :: (Monad m, Vector v a) => (Word -> m a) -> m (Chimera v a) Source #

Monadic version of tabulate.

Since: 0.2.0.0

tabulateFixM :: (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.

Since: 0.2.0.0

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'.

Since: 0.3.3.0

iterateM :: (Monad m, Vector v a) => (a -> m a) -> a -> m (Chimera v a) Source #

Monadic version of iterate.

Since: 0.3.0.0

unfoldrM :: (Monad m, Vector v b) => (a -> m (b, a)) -> a -> m (Chimera v b) Source #

Monadic version of unfoldr.

Since: 0.3.3.0

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 = zipWithSubvectors (zipBits (.&.)) ch1 ch2

mapSubvectors :: (Vector u a, Vector v b) => (u a -> v b) -> Chimera u a -> Chimera v b Source #

Map subvectors of a stream, using a given length-preserving function.

Since: 0.3.0.0

traverseSubvectors :: (Vector u a, Vector v b, Applicative m) => (u a -> m (v b)) -> Chimera u a -> m (Chimera v b) Source #

Traverse subvectors of a stream, using a given length-preserving function.

Be careful, because similar to tabulateM, only lazy monadic effects can be executed in a finite time: lazy state monad is fine, but strict one is not.

Since: 0.3.3.0

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

Deprecated: Use zipWithSubvectors instead

Since: 0.3.0.0

zipWithSubvectors :: (Vector u a, Vector v b, Vector w c) => (u a -> v b -> w c) -> Chimera u a -> Chimera v b -> Chimera w c Source #

Zip subvectors from two streams, using a given length-preserving function.

Since: 0.3.3.0

zipWithMSubvectors :: (Vector u a, Vector v b, Vector w c, Applicative m) => (u a -> v b -> m (w c)) -> Chimera u a -> Chimera v b -> m (Chimera w c) Source #

Zip subvectors from two streams, using a given monadic length-preserving function. Caveats for tabulateM and traverseSubvectors apply.

Since: 0.3.3.0

sliceSubvectors Source #

Arguments

:: Vector v a 
=> Int

How many initial elements to drop?

-> Int

How many subsequent elements to take?

-> Chimera v a 
-> [v a] 

Take a slice of Chimera, represented as a list on consecutive subvectors.

Since: 0.3.3.0