MemoTrie-0.6.4: Trie-based memo functions

Copyright(c) Conal Elliott 2008-2012
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.MemoTrie

Description

Trie-based memoizer

Adapted from sjanssen's paste: "a lazy trie", which I think is based on Ralf Hinze's paper "Memo Functions, Polytypically!".

You can automatically derive generic instances. for example:

{--}
import Data.MemoTrie
import GHC.Generics (Generic) 

data Color = RGB Int Int Int
           | NamedColor String 
 deriving (Generic) 

instance HasTrie Color where
  newtype (Color :->: b) = ColorTrie { unColorTrie :: Reg Color :->: b } 
  trie = trieGeneric ColorTrie 
  untrie = untrieGeneric unColorTrie
  enumerate = enumerateGeneric unColorTrie

see examples/Generic.hs, which can be run with:

$ cabal configure -fexamples && cabal run generic

Synopsis

Documentation

class HasTrie a where Source

Mapping from all elements of a to the results of some function

Associated Types

data (:->:) a :: * -> * infixr 0 Source

Representation of trie with domain type a

Methods

trie :: (a -> b) -> a :->: b Source

Create the trie for the entire domain of a function

untrie :: (a :->: b) -> a -> b Source

Convert a trie to a function, i.e., access a field of the trie

enumerate :: (a :->: b) -> [(a, b)] Source

List the trie elements. Order of keys (:: a) is always the same.

Instances

HasTrie Bool Source 
HasTrie Char Source 
HasTrie Int Source 
HasTrie Int8 Source 
HasTrie Int16 Source 
HasTrie Int32 Source 
HasTrie Int64 Source 
HasTrie Integer Source 
HasTrie Word Source 
HasTrie Word8 Source 
HasTrie Word16 Source 
HasTrie Word32 Source 
HasTrie Word64 Source 
HasTrie () Source 
HasTrie Void Source 
HasTrie x => HasTrie [x] Source 
HasTrie (V1 x) Source

just like void

HasTrie (U1 x) Source

just like ()

(HasTrie a, HasTrie b) => HasTrie (Either a b) Source 
(HasTrie a, HasTrie b) => HasTrie (a, b) Source 
HasTrie a => HasTrie (K1 i a x) Source

wraps a

(HasTrie (f x), HasTrie (g x)) => HasTrie ((:+:) f g x) Source

wraps Either (f x) (g x)

(HasTrie (f x), HasTrie (g x)) => HasTrie ((:*:) f g x) Source

wraps (f x, g x)

(HasTrie a, HasTrie b, HasTrie c) => HasTrie (a, b, c) Source 
HasTrie (f x) => HasTrie (M1 i t f x) Source

wraps f x

domain :: HasTrie a => [a] Source

Domain elements of a trie

idTrie :: HasTrie a => a :->: a Source

Identity trie

(@.@) :: (HasTrie a, HasTrie b) => (b :->: c) -> (a :->: b) -> a :->: c infixr 9 Source

Trie composition

memo :: HasTrie t => (t -> a) -> t -> a Source

Trie-based function memoizer

memo2 :: (HasTrie s, HasTrie t) => (s -> t -> a) -> s -> t -> a Source

Memoize a binary function, on its first argument and then on its second. Take care to exploit any partial evaluation.

memo3 :: (HasTrie r, HasTrie s, HasTrie t) => (r -> s -> t -> a) -> r -> s -> t -> a Source

Memoize a ternary function on successive arguments. Take care to exploit any partial evaluation.

mup :: HasTrie t => (b -> c) -> (t -> b) -> t -> c Source

Lift a memoizer to work with one more argument.

inTrie :: (HasTrie a, HasTrie c) => ((a -> b) -> c -> d) -> (a :->: b) -> c :->: d Source

Apply a unary function inside of a trie

inTrie2 :: (HasTrie a, HasTrie c, HasTrie e) => ((a -> b) -> (c -> d) -> e -> f) -> (a :->: b) -> (c :->: d) -> e :->: f Source

Apply a binary function inside of a trie

inTrie3 :: (HasTrie a, HasTrie c, HasTrie e, HasTrie g) => ((a -> b) -> (c -> d) -> (e -> f) -> g -> h) -> (a :->: b) -> (c :->: d) -> (e :->: f) -> g :->: h Source

Apply a ternary function inside of a trie

trieGeneric :: (Generic a, HasTrie (Reg a)) => ((Reg a :->: b) -> a :->: b) -> (a -> b) -> a :->: b Source

untrieGeneric :: (Generic a, HasTrie (Reg a)) => ((a :->: b) -> Reg a :->: b) -> (a :->: b) -> a -> b Source

enumerateGeneric :: (Generic a, HasTrie (Reg a)) => ((a :->: b) -> Reg a :->: b) -> (a :->: b) -> [(a, b)] Source

type Reg a = Rep a () Source

the data type in a regular form. "unlifted" generic representation. (i.e. is a unary type constructor).