MemoTrie-0.6.10: Trie-based memo functions
Copyright (c) Conal Elliott 2008-2016
License BSD3
Maintainer conal@conal.net
Stability experimental
Safe Haskell Safe-Inferred
Language Haskell2010

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:

{-# LANGUAGE DeriveGeneric, TypeOperators, TypeFamilies #-}
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

Instances details
HasTrie Bool Source #
Instance details

Defined in Data.MemoTrie

HasTrie Char Source #
Instance details

Defined in Data.MemoTrie

HasTrie Int Source #
Instance details

Defined in Data.MemoTrie

HasTrie Int8 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Int16 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Int32 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Int64 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Integer Source #
Instance details

Defined in Data.MemoTrie

HasTrie Word Source #
Instance details

Defined in Data.MemoTrie

HasTrie Word8 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Word16 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Word32 Source #
Instance details

Defined in Data.MemoTrie

HasTrie Word64 Source #
Instance details

Defined in Data.MemoTrie

HasTrie () Source #
Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) () :: Type -> Type Source #

Methods

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

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

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

HasTrie Void Source #
Instance details

Defined in Data.MemoTrie

HasTrie x => HasTrie [x] Source #
Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) [x] :: Type -> Type Source #

Methods

trie :: ([x] -> b) -> [x] :->: b Source #

untrie :: ([x] :->: b) -> [x] -> b Source #

enumerate :: ([x] :->: b) -> [([x], b)] Source #

HasTrie a => HasTrie ( Maybe a) Source #
Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ( Maybe a) :: Type -> Type Source #

( HasTrie a, HasTrie b) => HasTrie ( Either a b) Source #
Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ( Either a b) :: Type -> Type Source #

HasTrie ( V1 x) Source #

just like void

Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ( V1 x) :: Type -> Type Source #

HasTrie ( U1 x) Source #

just like ()

Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ( U1 x) :: Type -> Type Source #

( HasTrie a, HasTrie b) => HasTrie (a, b) Source #
Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) (a, b) :: Type -> Type Source #

Methods

trie :: ((a, b) -> b0) -> (a, b) :->: b0 Source #

untrie :: ((a, b) :->: b0) -> (a, b) -> b0 Source #

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

( HasTrie a, HasTrie b, HasTrie c) => HasTrie (a, b, c) Source #
Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) (a, b, c) :: Type -> Type Source #

Methods

trie :: ((a, b, c) -> b0) -> (a, b, c) :->: b0 Source #

untrie :: ((a, b, c) :->: b0) -> (a, b, c) -> b0 Source #

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

HasTrie a => HasTrie ( K1 i a x) Source #

wraps a

Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ( K1 i a x) :: Type -> Type Source #

Methods

trie :: ( K1 i a x -> b) -> K1 i a x :->: b Source #

untrie :: ( K1 i a x :->: b) -> K1 i a x -> b Source #

enumerate :: ( K1 i a x :->: b) -> [( K1 i a x, b)] Source #

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

wraps Either (f x) (g x)

Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ((f :+: g) x) :: Type -> Type Source #

Methods

trie :: ((f :+: g) x -> b) -> (f :+: g) x :->: b Source #

untrie :: ((f :+: g) x :->: b) -> (f :+: g) x -> b Source #

enumerate :: ((f :+: g) x :->: b) -> [((f :+: g) x, b)] Source #

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

wraps (f x, g x)

Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ((f :*: g) x) :: Type -> Type Source #

Methods

trie :: ((f :*: g) x -> b) -> (f :*: g) x :->: b Source #

untrie :: ((f :*: g) x :->: b) -> (f :*: g) x -> b Source #

enumerate :: ((f :*: g) x :->: b) -> [((f :*: g) x, b)] Source #

HasTrie (f x) => HasTrie ( M1 i t f x) Source #

wraps f x

Instance details

Defined in Data.MemoTrie

Associated Types

data (:->:) ( M1 i t f x) :: Type -> Type Source #

Methods

trie :: ( M1 i t f x -> b) -> M1 i t f x :->: b Source #

untrie :: ( M1 i t f x :->: b) -> M1 i t f x -> b Source #

enumerate :: ( M1 i t f x :->: b) -> [( M1 i t f x, b)] Source #

domain :: HasTrie a => [a] Source #

Domain elements of a 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 #

Generic -friendly default for trie

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

Generic -friendly default for untrie

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

Generic -friendly default for enumerate

type Reg a = Rep a () Source #

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

memoFix :: HasTrie a => ((a -> b) -> a -> b) -> a -> b Source #

Memoizing recursion. Use like fix .