monad-memo-0.5.0: Memoization monad transformer

Copyright(c) Eduard Sergeev 2013
LicenseBSD-style (see the file LICENSE)
Maintainereduard.sergeev@gmail.com
Stabilityexperimental
Portabilitynon-portable (multi-param classes, flexible instances)
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Memo.Vector.Expandable

Contents

Description

Vector-based MonadCache implementation which dynamically expands the vector during the computation to accomodate all requested keys. This implementation does not require to specify the length of the vector up front, but may be slower than Control.Monad.Memo.Vector.

Synopsis

VectorCache for boxed types

type VectorCache s e = Cache Vector s e Source #

MonadCache based on boxed vector

class MaybeLike e v => VectorMemo v e | v -> e Source #

This is just to be able to infer the type of the VectorCache element.

Instances
MaybeLike (Maybe v) v => VectorMemo v (Maybe v) Source # 
Instance details

Defined in Control.Monad.Memo.Vector.Instances

startEvalVectorMemo :: (PrimMonad m, VectorMemo v e) => VectorCache (PrimState m) e m a -> m a Source #

Evaluate computation using mutable boxed vector which dynamically grows to accomodate all requested keys

startRunVectorMemo :: (PrimMonad m, VectorMemo v e) => VectorCache (PrimState m) e m a -> m (a, Vector (PrimState m) e) Source #

Evaluate computation using mutable boxed vector which dynamically grows to accomodate all requested keys. This function also returns the final content of the vector cache

UVectorCache for unboxed types

type UVectorCache s e = Cache UVector s e Source #

MonadCache based on unboxed vector

class MaybeLike e v => UVectorMemo v e | v -> e Source #

This is just to be able to infer the type of the UVectorCache element.

Instances
MaybeLike v v => UVectorMemo v v Source # 
Instance details

Defined in Control.Monad.Memo.Vector.Instances

startEvalUVectorMemo :: (PrimMonad m, UVectorMemo v e, MVector UVector e) => UVectorCache (PrimState m) e m a -> m a Source #

Evaluate computation using mutable unboxed vector which dynamically grows to accomodate all requested keys

startRunUVectorMemo :: (PrimMonad m, UVectorMemo v e, MVector UVector e) => UVectorCache (PrimState m) e m a -> m (a, UVector (PrimState m) e) Source #

Evaluate computation using mutable unboxed vector which dynamically grows to accomodate all requested keys. This function also returns the final content of the vector cache

Generic functions for VectorCache

newtype Container vec Source #

Constructors

Container 

Fields

Instances
(PrimMonad m, PrimState m ~ s, MaybeLike e v, MVector c e) => MonadMemo Int v (Cache c s e m) Source # 
Instance details

Defined in Control.Monad.Memo.Vector.Expandable

Methods

memo :: (Int -> Cache c s e m v) -> Int -> Cache c s e m v Source #

(PrimMonad m, PrimState m ~ s, MaybeLike e v, MVector c e) => MonadCache Int v (Cache c s e m) Source # 
Instance details

Defined in Control.Monad.Memo.Vector.Expandable

Methods

lookup :: Int -> Cache c s e m (Maybe v) Source #

add :: Int -> v -> Cache c s e m () Source #

type Cache vec k e = StateCache (Container (vec k e)) Source #

Generic Vector-based memo cache

genericStartEvalVectorMemo :: (MaybeLike e v, PrimMonad m, MVector vec e) => Cache vec (PrimState m) e m a -> m a Source #

genericStartRunVectorMemo :: (MaybeLike e v, PrimMonad m, MVector vec e) => Cache vec (PrimState m) e m a -> m (a, vec (PrimState m) e) Source #