data-memocombinators-0.2: Combinators for building memo tables.

Stabilityexperimental
MaintainerLuke Palmer <lrpalmer@gmail.com>

Data.MemoCombinators

Description

This module provides combinators for building memo tables over various data types, so that the type of table can be customized depending on the application.

This module is designed to be imported qualified, eg.

 import qualified Data.MemoCombinators as Memo

Usage is straightforward: apply an object of type Memo a to a function of type a -> b, and get a memoized function of type a -> b. For example:

 fib = Memo.integral fib'
    where
    fib' 0 = 0
    fib' 1 = 1
    fib' x = fib (x-1) + fib (x-2)

Synopsis

Documentation

type Memo a = forall r. (a -> r) -> a -> rSource

The type of a memo table for functions of a.

memo2 :: Memo a -> Memo b -> (a -> b -> r) -> a -> b -> rSource

Memoize a two argument function (just apply the table directly for single argument functions).

memo3 :: Memo a -> Memo b -> Memo c -> (a -> b -> c -> r) -> a -> b -> c -> rSource

Memoize a three argument function.

memoSecond :: Memo b -> (a -> b -> r) -> a -> b -> rSource

Memoize the second argument of a function.

memoThird :: Memo c -> (a -> b -> c -> r) -> a -> b -> c -> rSource

Memoize the third argument of a function.

list :: Memo a -> Memo [a]Source

boundedList :: Int -> Memo a -> Memo [a]Source

Build a table which memoizes all lists of less than the given length.

either :: Memo a -> Memo b -> Memo (Either a b)Source

pair :: Memo a -> Memo b -> Memo (a, b)Source

switch :: (a -> Bool) -> Memo a -> Memo a -> Memo aSource

switch p a b uses the memo table a whenever p gives true and the memo table b whenever p gives false.

integral :: Integral a => Memo aSource

Memoize an integral type.

bits :: forall a. (Ord a, Bits a) => Memo aSource

Memoize an ordered type with a bits instance. Good for most integral types.

unsignedBits :: Bits a => Memo aSource

Memoize an unsigned type with a bits instance. Good for nonnegative integral types. Warning: if a negative Integer is given to an unsignedBits-ized function, it will loop forever.

type RangeMemo a = (a, a) -> Memo aSource

The type of builders for ranged tables; takes a lower bound and an upper bound, and returns a memo table for that range.

arrayRange :: Ix a => RangeMemo aSource

Build a memo table for a range using a flat array. If items are given outside the range, don't memoize.

unsafeArrayRange :: Ix a => RangeMemo aSource

Build a memo table for a range using a flat array. If items are given outside the range, behavior is undefined.

chunks :: Ix a => RangeMemo a -> [(a, a)] -> Memo aSource

Given a list of ranges, (lazily) build a memo table for each one and combine them using linear search.