functor-combo-0.3.6: Functor combinators with tries & zippers

Copyright(c) Conal Elliott 2010
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

FunctorCombo.NonstrictMemo

Description

Synopsis

Documentation

class Functor (STrie k) => HasTrie k where Source

Domain types with associated memo tries

Associated Types

type STrie k :: * -> * Source

Representation of trie with domain type a

Methods

sTrie :: (k -> v) -> k :-> v Source

Create the trie for the entire domain of a function

sUntrie :: HasLub v => (k :-> v) -> k -> v Source

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

Instances

HasTrie Bool 
HasTrie Int 
HasTrie Integer 
HasTrie () 
HasTrie a => HasTrie [a] 
HasTrie a => HasTrie (Id a) 
HasTrie a => HasTrie (Lift a) 
(HasTrie a, HasTrie ((:->:) a b), HasLub b) => HasTrie (a -> b) 
(HasTrie a, HasTrie b) => HasTrie (Either a b) 
(HasTrie a, HasTrie b) => HasTrie (a, b) 
HasTrie x => HasTrie (Const x a) 
(HasTrie a, HasTrie b) => HasTrie ((:+!) a b) 
(HasTrie a, HasTrie b) => HasTrie ((:*!) a b) 
(HasTrie a, HasTrie b, HasTrie c) => HasTrie (a, b, c) 
HasTrie (g (f a)) => HasTrie ((:.) g f a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:+:!) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:*:!) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:+:) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:*:) f g a) 
(HasTrie a, HasTrie b, HasTrie c, HasTrie d) => HasTrie (a, b, c, d) 

type (:->:) k v = Trie k v infixr 0 Source

memo :: HasLub v => HasTrie k => Unop (k -> v) Source

Trie-based function memoizer

memo2 :: HasLub a => (HasTrie s, HasTrie t) => Unop (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 :: HasLub a => (HasTrie r, HasTrie s, HasTrie t) => Unop (r -> s -> t -> a) Source

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