| 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
- class HasTrie a where
- data family (:->:) a :: Type -> Type
- domain :: HasTrie a => [a]
- idTrie :: HasTrie a => a :->: a
- (@.@) :: (HasTrie a, HasTrie b) => (b :->: c) -> (a :->: b) -> a :->: c
- memo :: HasTrie t => (t -> a) -> t -> a
- memo2 :: (HasTrie s, HasTrie t) => (s -> t -> a) -> s -> t -> a
- memo3 :: (HasTrie r, HasTrie s, HasTrie t) => (r -> s -> t -> a) -> r -> s -> t -> a
- mup :: HasTrie t => (b -> c) -> (t -> b) -> t -> c
- inTrie :: (HasTrie a, HasTrie c) => ((a -> b) -> c -> d) -> (a :->: b) -> c :->: d
- inTrie2 :: (HasTrie a, HasTrie c, HasTrie e) => ((a -> b) -> (c -> d) -> e -> f) -> (a :->: b) -> (c :->: d) -> e :->: f
- 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
- trieGeneric :: (Generic a, HasTrie (Reg a)) => ((Reg a :->: b) -> a :->: b) -> (a -> b) -> a :->: b
- untrieGeneric :: (Generic a, HasTrie (Reg a)) => ((a :->: b) -> Reg a :->: b) -> (a :->: b) -> a -> b
- enumerateGeneric :: (Generic a, HasTrie (Reg a)) => ((a :->: b) -> Reg a :->: b) -> (a :->: b) -> [(a, b)]
- type Reg a = Rep a ()
- memoFix :: HasTrie a => ((a -> b) -> a -> b) -> a -> b
Documentation
Mapping from all elements of a to the results of some function
Methods
trie :: (a -> b) -> a :->: b #
Create the trie for the entire domain of a function
untrie :: (a :->: b) -> a -> b #
Convert a trie to a function, i.e., access a field of the trie
enumerate :: (a :->: b) -> [(a, b)] #
List the trie elements. Order of keys (:: a) is always the same.
Instances
| HasTrie Void # | |||||
| HasTrie Int16 # | |||||
| HasTrie Int32 # | |||||
| HasTrie Int64 # | |||||
| HasTrie Int8 # | |||||
| HasTrie Word16 # | |||||
| HasTrie Word32 # | |||||
| HasTrie Word64 # | |||||
| HasTrie Word8 # | |||||
| HasTrie Integer # | |||||
| HasTrie () # | |||||
| HasTrie Bool # | |||||
| HasTrie Char # | |||||
| HasTrie Int # | |||||
| HasTrie Word # | |||||
| HasTrie a => HasTrie (Maybe a) # | |||||
| HasTrie x => HasTrie [x] # | |||||
| (HasTrie a, HasTrie b) => HasTrie (Either a b) # | |||||
Defined in Data.MemoTrie Associated Types
| |||||
| HasTrie (U1 x) # | just like | ||||
| HasTrie (V1 x) # | just like | ||||
| (HasTrie a, HasTrie b) => HasTrie (a, b) # | |||||
| (HasTrie a, HasTrie b, HasTrie c) => HasTrie (a, b, c) # | |||||
Defined in Data.MemoTrie Associated Types
| |||||
| (HasTrie (f x), HasTrie (g x)) => HasTrie ((f :*: g) x) # | wraps | ||||
Defined in Data.MemoTrie Associated Types
| |||||
| (HasTrie (f x), HasTrie (g x)) => HasTrie ((f :+: g) x) # | wraps | ||||
Defined in Data.MemoTrie Associated Types
| |||||
| HasTrie a => HasTrie (K1 i a x) # | wraps | ||||
| HasTrie (f x) => HasTrie (M1 i t f x) # | wraps | ||||
Defined in Data.MemoTrie Associated Types
| |||||
data family (:->:) a :: Type -> Type infixr 0 #
Representation of trie with domain type a
Instances
| HasTrie a => Applicative ((:->:) a) # | |
| HasTrie a => Functor ((:->:) a) # | |
| HasTrie a => Monad ((:->:) a) # | |
| (HasTrie a, Monoid b) => Monoid (a :->: b) # | |
| (HasTrie a, Semigroup b) => Semigroup (a :->: b) # | |
| (HasTrie a, Show a, Show b) => Show (a :->: b) # | |
| (HasTrie a, Eq b) => Eq (a :->: b) # | |
| Newtype (Void :->: a) # | |
| Newtype (Either a b :->: x) # | |
| Newtype (Maybe a :->: x) # | |
| Newtype ((a, b) :->: x) # | |
| Newtype (() :->: a) # | |
| Newtype (Bool :->: a) # | |
| data Void :->: a # | |
Defined in Data.MemoTrie | |
| newtype Int16 :->: a # | |
| newtype Int32 :->: a # | |
| newtype Int64 :->: a # | |
| newtype Int8 :->: a # | |
| newtype Word16 :->: a # | |
Defined in Data.MemoTrie | |
| newtype Word32 :->: a # | |
Defined in Data.MemoTrie | |
| newtype Word64 :->: a # | |
Defined in Data.MemoTrie | |
| newtype Word8 :->: a # | |
| newtype Integer :->: a # | |
Defined in Data.MemoTrie | |
| newtype () :->: a # | |
Defined in Data.MemoTrie | |
| data Bool :->: x # | |
Defined in Data.MemoTrie | |
| newtype Char :->: a # | |
| newtype Int :->: a # | |
| newtype Word :->: a # | |
| data (Maybe a) :->: b # | |
Defined in Data.MemoTrie | |
| newtype [x] :->: a # | |
Defined in Data.MemoTrie | |
| data (Either a b) :->: x # | |
Defined in Data.MemoTrie | |
| newtype (U1 x) :->: b # | |
Defined in Data.MemoTrie | |
| data (V1 x) :->: b # | |
Defined in Data.MemoTrie | |
| newtype (a, b) :->: x # | |
Defined in Data.MemoTrie | |
| type O (Void :->: a) # | |
Defined in Data.MemoTrie | |
| type O (Either a b :->: x) # | |
| type O (Maybe a :->: x) # | |
Defined in Data.MemoTrie | |
| type O ((a, b) :->: x) # | |
Defined in Data.MemoTrie | |
| type O (() :->: a) # | |
Defined in Data.MemoTrie | |
| type O (Bool :->: a) # | |
Defined in Data.MemoTrie | |
| newtype (a, b, c) :->: x # | |
Defined in Data.MemoTrie | |
| newtype ((f :*: g) x) :->: b # | |
Defined in Data.MemoTrie | |
| newtype ((f :+: g) x) :->: b # | |
Defined in Data.MemoTrie | |
| newtype (K1 i a x) :->: b # | |
Defined in Data.MemoTrie | |
| newtype (M1 i t f x) :->: b # | |
Defined in Data.MemoTrie | |
memo2 :: (HasTrie s, HasTrie t) => (s -> t -> a) -> s -> t -> a #
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 #
Memoize a ternary function on successive arguments. Take care to exploit any partial evaluation.
inTrie :: (HasTrie a, HasTrie c) => ((a -> b) -> c -> d) -> (a :->: b) -> c :->: d #
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 #
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 #
Apply a ternary function inside of a trie
trieGeneric :: (Generic a, HasTrie (Reg a)) => ((Reg a :->: b) -> a :->: b) -> (a -> b) -> a :->: b #
untrieGeneric :: (Generic a, HasTrie (Reg a)) => ((a :->: b) -> Reg a :->: b) -> (a :->: b) -> a -> b #
enumerateGeneric :: (Generic a, HasTrie (Reg a)) => ((a :->: b) -> Reg a :->: b) -> (a :->: b) -> [(a, b)] #
the data type in a regular form. "unlifted" generic representation. (i.e. is a unary type constructor).