hashcons-0.1.0: Hash-consing and memoisation

Copyright© 2018 Andy Morris
LicenseBSD-3-Clause
Maintainerhello@andy-morris.xyz
Stabilityexperimental
PortabilityTODO
Safe HaskellNone
LanguageHaskell2010

Data.HashCons.Memo

Contents

Description

Memoisation, using hash-consing as a way to identify arguments.

Synopsis

Memo-suitable arguments

class (Eq (Key k), Hashable (Key k)) => MemoArg k where Source #

Types which can be arguments to a memo function. An empty instance assumes that a type is its own key, and can't run finalizers. The latter is the case for ordinary Haskell datatypes.

(TODO: add instances for everything in base)

Associated Types

type Key k :: Type Source #

A key which uniquely identifies a value. Defaults to the value itself. Otherwise, it should be something with fast equality and hashing, and must really be a unique identifier.

type CanFinalize k :: Bool Source #

Whether k can reliably run finalizers. (Most datatypes can't; see the documentation for Weak for details.)

Methods

key :: k -> Key k Source #

Extract the key. Defaults to the identity function for where Key k ~ k.

key :: Key k ~ k => k -> Key k Source #

Extract the key. Defaults to the identity function for where Key k ~ k.

tryAddFinalizer :: k -> Finalizer -> IO () Source #

Add a finalizer, if possible; otherwise, do nothing. Defaults to doing nothing, for when CanFinalize k ~ 'False.

Instances

MemoArg Bool Source # 

Associated Types

type Key Bool :: Type Source #

type CanFinalize Bool :: Bool Source #

MemoArg Char Source # 

Associated Types

type Key Char :: Type Source #

type CanFinalize Char :: Bool Source #

MemoArg Double Source # 

Associated Types

type Key Double :: Type Source #

type CanFinalize Double :: Bool Source #

MemoArg Float Source # 

Associated Types

type Key Float :: Type Source #

type CanFinalize Float :: Bool Source #

MemoArg Int Source # 

Associated Types

type Key Int :: Type Source #

type CanFinalize Int :: Bool Source #

MemoArg Int8 Source # 

Associated Types

type Key Int8 :: Type Source #

type CanFinalize Int8 :: Bool Source #

MemoArg Int16 Source # 

Associated Types

type Key Int16 :: Type Source #

type CanFinalize Int16 :: Bool Source #

MemoArg Int32 Source # 

Associated Types

type Key Int32 :: Type Source #

type CanFinalize Int32 :: Bool Source #

MemoArg Int64 Source # 

Associated Types

type Key Int64 :: Type Source #

type CanFinalize Int64 :: Bool Source #

MemoArg Integer Source # 
MemoArg Natural Source # 
MemoArg Ordering Source # 
MemoArg Word Source # 

Associated Types

type Key Word :: Type Source #

type CanFinalize Word :: Bool Source #

MemoArg Word8 Source # 

Associated Types

type Key Word8 :: Type Source #

type CanFinalize Word8 :: Bool Source #

MemoArg Word16 Source # 

Associated Types

type Key Word16 :: Type Source #

type CanFinalize Word16 :: Bool Source #

MemoArg Word32 Source # 

Associated Types

type Key Word32 :: Type Source #

type CanFinalize Word32 :: Bool Source #

MemoArg Word64 Source # 

Associated Types

type Key Word64 :: Type Source #

type CanFinalize Word64 :: Bool Source #

MemoArg () Source # 

Associated Types

type Key () :: Type Source #

type CanFinalize () :: Bool Source #

Methods

key :: () -> Key () Source #

tryAddFinalizer :: () -> Finalizer -> IO () Source #

MemoArg Unique Source # 

Associated Types

type Key Unique :: Type Source #

type CanFinalize Unique :: Bool Source #

MemoArg Version Source # 
MemoArg ThreadId Source # 
MemoArg All Source # 

Associated Types

type Key All :: Type Source #

type CanFinalize All :: Bool Source #

MemoArg Any Source # 

Associated Types

type Key Any :: Type Source #

type CanFinalize Any :: Bool Source #

MemoArg ByteString Source # 
MemoArg ByteString Source # 
MemoArg Text Source # 

Associated Types

type Key Text :: Type Source #

type CanFinalize Text :: Bool Source #

Methods

key :: Text -> Key Text Source #

tryAddFinalizer :: Text -> Finalizer -> IO () Source #

MemoArg Text Source # 

Associated Types

type Key Text :: Type Source #

type CanFinalize Text :: Bool Source #

Methods

key :: Text -> Key Text Source #

tryAddFinalizer :: Text -> Finalizer -> IO () Source #

MemoArg a => MemoArg [a] Source #

doesn't add finalizer to elements

Associated Types

type Key [a] :: Type Source #

type CanFinalize [a] :: Bool Source #

Methods

key :: [a] -> Key [a] Source #

tryAddFinalizer :: [a] -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Maybe a) Source #

tries to add finalizer to contents, if any

Associated Types

type Key (Maybe a) :: Type Source #

type CanFinalize (Maybe a) :: Bool Source #

Methods

key :: Maybe a -> Key (Maybe a) Source #

tryAddFinalizer :: Maybe a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Ratio a) Source # 

Associated Types

type Key (Ratio a) :: Type Source #

type CanFinalize (Ratio a) :: Bool Source #

Methods

key :: Ratio a -> Key (Ratio a) Source #

tryAddFinalizer :: Ratio a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Fixed a) Source # 

Associated Types

type Key (Fixed a) :: Type Source #

type CanFinalize (Fixed a) :: Bool Source #

Methods

key :: Fixed a -> Key (Fixed a) Source #

tryAddFinalizer :: Fixed a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Min a) Source # 

Associated Types

type Key (Min a) :: Type Source #

type CanFinalize (Min a) :: Bool Source #

Methods

key :: Min a -> Key (Min a) Source #

tryAddFinalizer :: Min a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Max a) Source # 

Associated Types

type Key (Max a) :: Type Source #

type CanFinalize (Max a) :: Bool Source #

Methods

key :: Max a -> Key (Max a) Source #

tryAddFinalizer :: Max a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (First a) Source # 

Associated Types

type Key (First a) :: Type Source #

type CanFinalize (First a) :: Bool Source #

Methods

key :: First a -> Key (First a) Source #

tryAddFinalizer :: First a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Last a) Source # 

Associated Types

type Key (Last a) :: Type Source #

type CanFinalize (Last a) :: Bool Source #

Methods

key :: Last a -> Key (Last a) Source #

tryAddFinalizer :: Last a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Option a) Source # 

Associated Types

type Key (Option a) :: Type Source #

type CanFinalize (Option a) :: Bool Source #

Methods

key :: Option a -> Key (Option a) Source #

tryAddFinalizer :: Option a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (NonEmpty a) Source #

doesn't add finalizer to elements

Associated Types

type Key (NonEmpty a) :: Type Source #

type CanFinalize (NonEmpty a) :: Bool Source #

MemoArg (StableName a) Source # 

Associated Types

type Key (StableName a) :: Type Source #

type CanFinalize (StableName a) :: Bool Source #

MemoArg a => MemoArg (Identity a) Source # 

Associated Types

type Key (Identity a) :: Type Source #

type CanFinalize (Identity a) :: Bool Source #

MemoArg a => MemoArg (Dual a) Source # 

Associated Types

type Key (Dual a) :: Type Source #

type CanFinalize (Dual a) :: Bool Source #

Methods

key :: Dual a -> Key (Dual a) Source #

tryAddFinalizer :: Dual a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Sum a) Source # 

Associated Types

type Key (Sum a) :: Type Source #

type CanFinalize (Sum a) :: Bool Source #

Methods

key :: Sum a -> Key (Sum a) Source #

tryAddFinalizer :: Sum a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Product a) Source # 

Associated Types

type Key (Product a) :: Type Source #

type CanFinalize (Product a) :: Bool Source #

MemoArg a => MemoArg (First a) Source # 

Associated Types

type Key (First a) :: Type Source #

type CanFinalize (First a) :: Bool Source #

Methods

key :: First a -> Key (First a) Source #

tryAddFinalizer :: First a -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Last a) Source # 

Associated Types

type Key (Last a) :: Type Source #

type CanFinalize (Last a) :: Bool Source #

Methods

key :: Last a -> Key (Last a) Source #

tryAddFinalizer :: Last a -> Finalizer -> IO () Source #

MemoArg (HC a) Source # 

Associated Types

type Key (HC a) :: Type Source #

type CanFinalize (HC a) :: Bool Source #

Methods

key :: HC a -> Key (HC a) Source #

tryAddFinalizer :: HC a -> Finalizer -> IO () Source #

(MemoArg a, MemoArg b) => MemoArg (Either a b) Source #

tries to add finalizer to contents

Associated Types

type Key (Either a b) :: Type Source #

type CanFinalize (Either a b) :: Bool Source #

Methods

key :: Either a b -> Key (Either a b) Source #

tryAddFinalizer :: Either a b -> Finalizer -> IO () Source #

MemoArg (TypeRep * a) Source # 

Associated Types

type Key (TypeRep * a) :: Type Source #

type CanFinalize (TypeRep * a) :: Bool Source #

(MemoArg a, MemoArg b) => MemoArg (a, b) Source #

tries to add finalizer to both elements

Associated Types

type Key (a, b) :: Type Source #

type CanFinalize (a, b) :: Bool Source #

Methods

key :: (a, b) -> Key (a, b) Source #

tryAddFinalizer :: (a, b) -> Finalizer -> IO () Source #

MemoArg (Proxy * a) Source # 

Associated Types

type Key (Proxy * a) :: Type Source #

type CanFinalize (Proxy * a) :: Bool Source #

Methods

key :: Proxy * a -> Key (Proxy * a) Source #

tryAddFinalizer :: Proxy * a -> Finalizer -> IO () Source #

(MemoArg a, MemoArg b, MemoArg c) => MemoArg (a, b, c) Source #

tries to add finalizer to all elements

Associated Types

type Key (a, b, c) :: Type Source #

type CanFinalize (a, b, c) :: Bool Source #

Methods

key :: (a, b, c) -> Key (a, b, c) Source #

tryAddFinalizer :: (a, b, c) -> Finalizer -> IO () Source #

MemoArg a => MemoArg (Const * a b) Source # 

Associated Types

type Key (Const * a b) :: Type Source #

type CanFinalize (Const * a b) :: Bool Source #

Methods

key :: Const * a b -> Key (Const * a b) Source #

tryAddFinalizer :: Const * a b -> Finalizer -> IO () Source #

MemoArg (f a) => MemoArg (Alt * f a) Source # 

Associated Types

type Key (Alt * f a) :: Type Source #

type CanFinalize (Alt * f a) :: Bool Source #

Methods

key :: Alt * f a -> Key (Alt * f a) Source #

tryAddFinalizer :: Alt * f a -> Finalizer -> IO () Source #

(MemoArg (f a), MemoArg (g a)) => MemoArg (Product * f g a) Source #

tries to add finalizer to both elements

Associated Types

type Key (Product * f g a) :: Type Source #

type CanFinalize (Product * f g a) :: Bool Source #

Methods

key :: Product * f g a -> Key (Product * f g a) Source #

tryAddFinalizer :: Product * f g a -> Finalizer -> IO () Source #

(MemoArg (f a), MemoArg (g a)) => MemoArg (Sum * f g a) Source #

tries to add finalizer to contents

Associated Types

type Key (Sum * f g a) :: Type Source #

type CanFinalize (Sum * f g a) :: Bool Source #

Methods

key :: Sum * f g a -> Key (Sum * f g a) Source #

tryAddFinalizer :: Sum * f g a -> Finalizer -> IO () Source #

MemoArg (f (g a)) => MemoArg (Compose * * f g a) Source # 

Associated Types

type Key (Compose * * f g a) :: Type Source #

type CanFinalize (Compose * * f g a) :: Bool Source #

Methods

key :: Compose * * f g a -> Key (Compose * * f g a) Source #

tryAddFinalizer :: Compose * * f g a -> Finalizer -> IO () Source #

Memoising functions

uncheckedMemo :: MemoArg a => (a -> b) -> a -> b Source #

Memoise a function, without checking that the memo table can be pruned. If it can't, then it will continue to grow throughout the program's run.

memo :: (MemoArg a, CanFinalize a ~ True) => (a -> b) -> a -> b Source #

Memoise a function, ensuring that the memo table can be pruned.

Nested memoisation

It is possible to memoise a multiple-argument function by nesting calls to memo or uncheckedMemo, like so:

foo :: HC Beep -> HC Boop -> HC Bing -> HC Blah

memoFoo :: HC Beep -> HC Boop -> HC Bing -> HC Blah
memoFoo = memo $ \x -> memo $ \y -> memo $ foo x y

The functions memo2 to memo4 do this, with the first use being (checked) memo and the other(s) being uncheckedMemo.

The user can use this pattern to write variations of a higher arity, or to check whichever arguments are desired.

Recommendations

  • If possible, the first (or only) argument to a memoised function should be able to run finalisers (e.g., HC): if a call to uncheckedMemo is nested inside a use of memo, then whole tables will be dropped by the outer memo's finalizers when no longer needed, even though they might not shrink before this time. Therefore, an outermost memo ensures that the memory usage is kept in check.
  • If the least-long-lived arguments come first, then the pruning will be more effective.

memo2 :: (MemoArg a, MemoArg b, CanFinalize a ~ True) => (a -> b -> c) -> a -> b -> c Source #

Memoise a binary function, checking that the outer table can be pruned.

memo3 :: (MemoArg a, MemoArg b, MemoArg c, CanFinalize a ~ True) => (a -> b -> c -> d) -> a -> b -> c -> d Source #

Memoise a ternary function, checking that the outermost table can be pruned.

memo4 :: (MemoArg a, MemoArg b, MemoArg c, MemoArg d, CanFinalize a ~ True) => (a -> b -> c -> d -> e) -> a -> b -> c -> d -> e Source #

Memoise a quaternary function, checking that the outermost table can be pruned.

uncheckedMemo2 :: (MemoArg a, MemoArg b) => (a -> b -> c) -> a -> b -> c Source #

Memoise a binary function, without checking that the outer table can be pruned.

uncheckedMemo3 :: (MemoArg a, MemoArg b, MemoArg c) => (a -> b -> c -> d) -> a -> b -> c -> d Source #

Memoise a ternary function, without checking that the outermost table can be pruned.

uncheckedMemo4 :: (MemoArg a, MemoArg b, MemoArg c, MemoArg d) => (a -> b -> c -> d -> e) -> a -> b -> c -> d -> e Source #

Memoise a quaternary function, without checking that the outermost table can be pruned.