Stability | experimental |
---|---|
Maintainer | Luke Palmer <lrpalmer@gmail.com> |
Safe Haskell | Safe-Inferred |
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)
- type Memo a = forall r. (a -> r) -> a -> r
- wrap :: (a -> b) -> (b -> a) -> Memo a -> Memo b
- memo2 :: Memo a -> Memo b -> (a -> b -> r) -> a -> b -> r
- memo3 :: Memo a -> Memo b -> Memo c -> (a -> b -> c -> r) -> a -> b -> c -> r
- memoSecond :: Memo b -> (a -> b -> r) -> a -> b -> r
- memoThird :: Memo c -> (a -> b -> c -> r) -> a -> b -> c -> r
- bool :: Memo Bool
- char :: Memo Char
- list :: Memo a -> Memo [a]
- boundedList :: Int -> Memo a -> Memo [a]
- either :: Memo a -> Memo b -> Memo (Either a b)
- maybe :: Memo a -> Memo (Maybe a)
- unit :: Memo ()
- pair :: Memo a -> Memo b -> Memo (a, b)
- enum :: Enum a => Memo a
- integral :: Integral a => Memo a
- bits :: (Num a, Ord a, Bits a) => Memo a
- switch :: (a -> Bool) -> Memo a -> Memo a -> Memo a
- type RangeMemo a = (a, a) -> Memo a
- arrayRange :: Ix a => RangeMemo a
- unsafeArrayRange :: Ix a => RangeMemo a
- chunks :: Ix a => RangeMemo a -> [(a, a)] -> Memo a
Documentation
wrap :: (a -> b) -> (b -> a) -> Memo a -> Memo bSource
Given a memoizer for a and an isomorphism between a and b, build a memoizer for b.
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.
boundedList :: Int -> Memo a -> Memo [a]Source
Build a table which memoizes all lists of less than the given length.
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.
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.