monad-memo-0.4.0: Memoization monad transformer

Portabilitynon-portable (multi-param classes, flexible instances)
Stabilityexperimental
Maintainereduard.sergeev@gmail.com
Safe HaskellNone

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 eSource

MonadCache based on boxed vector

class MaybeLike e v => VectorMemo v e | v -> eSource

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

Instances

MaybeLike (Maybe v) v => VectorMemo v (Maybe v) 

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

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 eSource

MonadCache based on unboxed vector

class MaybeLike e v => UVectorMemo v e | v -> eSource

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

Instances

MaybeLike v v => UVectorMemo v v 

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

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

toVector :: vec
 

Instances

(PrimMonad m, ~ * (PrimState m) s, MaybeLike e v, MVector c e) => MonadMemo Int v (Cache c s e m) 
(PrimMonad m, ~ * (PrimState m) s, MaybeLike e v, MVector c e) => MonadCache Int v (Cache c s e m) 

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 aSource

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