memoize-0.7: A memoization library

Safe HaskellNone
LanguageHaskell98

Data.Function.Memoize

Contents

Description

A function memoization library.

This includes a class for memoizable argument types and a Template Haskell expander for deriving instances of the class.

Note that most memoization in this style relies on assumptions about the implementation of non-strictness (as laziness) that are not guaranteed by the semantics. However, it appears to work.

Synopsis

Memoization class

class Memoizable a where Source

A memoization class. An instance Memoizable T for some type T means that that memoize method can memoize for parameters of type T.

Methods

memoize :: (a -> v) -> a -> v Source

Instances

Memoizable Bool 
Memoizable Char 
Memoizable Int 
Memoizable Integer 
Memoizable Ordering 
Memoizable () 
Memoizable a => Memoizable [a] 
Memoizable a => Memoizable (Maybe a) 
(Eq a, Bounded a, Enum a, Memoizable b) => Memoizable (a -> b) 
(Memoizable a, Memoizable b) => Memoizable (Either a b) 
(Memoizable a, Memoizable b) => Memoizable (a, b) 
(Memoizable a, Memoizable b, Memoizable c) => Memoizable (a, b, c) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d) => Memoizable (a, b, c, d) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e) => Memoizable (a, b, c, d, e) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f) => Memoizable (a, b, c, d, e, f) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g) => Memoizable (a, b, c, d, e, f, g) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g, Memoizable h) => Memoizable (a, b, c, d, e, f, g, h) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g, Memoizable h, Memoizable i) => Memoizable (a, b, c, d, e, f, g, h, i) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g, Memoizable h, Memoizable i, Memoizable j) => Memoizable (a, b, c, d, e, f, g, h, i, j) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g, Memoizable h, Memoizable i, Memoizable j, Memoizable k) => Memoizable (a, b, c, d, e, f, g, h, i, j, k) 
(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g, Memoizable h, Memoizable i, Memoizable j, Memoizable k, Memoizable l) => Memoizable (a, b, c, d, e, f, g, h, i, j, k, l) 

Operations

Higher-arity memoize

memoize2 :: (Memoizable a, Memoizable b) => (a -> b -> v) -> a -> b -> v Source

Memoize a two argument function

memoize3 :: (Memoizable a, Memoizable b, Memoizable c) => (a -> b -> c -> v) -> a -> b -> c -> v Source

Memoize a three argument function

memoize4 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d) => (a -> b -> c -> d -> v) -> a -> b -> c -> d -> v Source

Memoize a four argument function

memoize5 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e) => (a -> b -> c -> d -> e -> v) -> a -> b -> c -> d -> e -> v Source

Memoize a five argument function

memoize6 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f) => (a -> b -> c -> d -> e -> f -> v) -> a -> b -> c -> d -> e -> f -> v Source

Memoize a six argument function

memoize7 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g) => (a -> b -> c -> d -> e -> f -> g -> v) -> a -> b -> c -> d -> e -> f -> g -> v Source

Memoize a seven argument function

Memoizing open recursion

memoFix :: Memoizable a => ((a -> v) -> a -> v) -> a -> v Source

Memoizes the least fixed point of a function. This is like fix, but it passes the fixed function a memoized version of itself, so this memoizes using all recursive calls as well.

memoFix2 :: (Memoizable a, Memoizable b) => ((a -> b -> v) -> a -> b -> v) -> a -> b -> v Source

Two argument version of memoFix.

memoFix3 :: (Memoizable a, Memoizable b, Memoizable c) => ((a -> b -> c -> v) -> a -> b -> c -> v) -> a -> b -> c -> v Source

Three argument version of memoFix.

memoFix4 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d) => ((a -> b -> c -> d -> v) -> a -> b -> c -> d -> v) -> a -> b -> c -> d -> v Source

Four argument version of memoFix.

memoFix5 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e) => ((a -> b -> c -> d -> e -> v) -> a -> b -> c -> d -> e -> v) -> a -> b -> c -> d -> e -> v Source

Five argument version of memoFix.

memoFix6 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f) => ((a -> b -> c -> d -> e -> f -> v) -> a -> b -> c -> d -> e -> f -> v) -> a -> b -> c -> d -> e -> f -> v Source

Six argument version of memoFix.

memoFix7 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g) => ((a -> b -> c -> d -> e -> f -> g -> v) -> a -> b -> c -> d -> e -> f -> g -> v) -> a -> b -> c -> d -> e -> f -> g -> v Source

Seven argument version of memoFix.

Tracing memoization

traceMemoize :: (Memoizable a, Show a) => (a -> b) -> a -> b Source

Give a one-argument function whose argument satisfies Show, this memoizes the function such that the argument is shown (using trace) only when the function has to be applied, as opposed to when the answer is available in the memo cache.

For making instances for finite types

memoizeFinite :: (Enum a, Bounded a) => (a -> v) -> a -> v Source

Can be used to memoize over any "finite" type satisfying Enum and Bounded. This builds a binary search tree, treating the memoized type as isomorphic to a range of Int, so it will be only as efficient as toEnum, fromEnum, succ, and pred.

This can be used to make instances for finite types. For example, the instances for Int and Char are declared as:

  instance Memoizable Int where memoize = memoizeFinite
  instance Memoizable Char where memoize = memoizeFinite

Deriving Memoizable

deriveMemoizable :: Name -> Q [Dec] Source

To derive Memoizable instances for the given data types. In the simplest usage, to derive Memoizable for an algebraic datatype named T, write:

  deriveMemoizable ''T

This assumes that all the type parameters of T that are not annotated with a kind other than * should be listed as requiring Memoizable instances in the instance context. For example, given a data type declared as

  data T a (b :: * -> *) c = ...

the generated instance will look like

  instance (Memoizable a, Memoizable c) =>
           Memoizable (T a b c) where ...

For more precise control over the context, use deriveMemoizableParams.

N.B.: The TemplateHaskell language extension must be enabled to use this function.

deriveMemoizableParams :: Name -> [Int] -> Q [Dec] Source

Like deriveMemoizable but takes a second argument, which is a list of Ints to specify which type parameters of the type should be mentioned in the context. For example, given the same definition for T as above, we can write

   deriveMemoizableParams ''T [3]

to leave the first parameter of T out of the context and show only the third, yielding the instance

  instance Memoizable c => Memoizable (T a b c) where ...

N.B.: The TemplateHaskell language extension must be enabled to use this function.

deriveMemoize :: Name -> ExpQ Source

In cases where neither deriveMemoizable nor deriveMemoizableParams can figure out the right context for an instance declaration, one can declare the instance manually and use this function to derive the method body for memoize. For example, suppose that a data type T is defined as:

  data T a b = T (a -> Bool) b

For T a b to be memoizable, a -> Bool must be, and based on the instance for '(->)', this means that a must satisfy Bounded and Enum, so deriveMemoizable cannot build the right context for the Memoizable instance. Instead, one can write:

  instance (Enum a, Bounded a, Memoizable b) =>
           Memoizable (T a b) where
    memoize = $(deriveMemoize ''T)