Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Data.Registry.Internal.Cache
Contents
Synopsis
- cacheAt :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Text -> m a -> m a
- singleton :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => m a -> m a
- newtype Cache = Cache (MVar (Map Text Cached))
- data Cached = Cached {}
- emptyCached :: Cached
- newCache :: MonadIO m => m Cache
- askCache :: MonadReader Cache m => m Cache
- data Key
- cacheAtKey :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Key -> m a -> m a
- getCached :: (Typeable a, MonadIO m, MonadReader Cache m) => Key -> m (Maybe a)
- setCached :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Key -> a -> m ()
- getCachedValue :: forall a m. (Typeable a, MonadIO m) => Key -> Cache -> m (Maybe a)
- cacheDynValue :: Key -> Dynamic -> Maybe Cached -> Maybe Cached
- getDynValue :: Key -> Cached -> Maybe Dynamic
- makeTypeText :: forall a. Typeable a => Text
EXPORTED FUNCTIONS
cacheAt :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Text -> m a -> m a Source #
Cache an effectful value with a given text key so that the value is not recreated for the same key
singleton :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => m a -> m a Source #
Cache an effectful value by using its type as the cache key
IMPLEMENTATION
A cache for created values, with a map from the textual representation of a type to various cached values
Instances
Cache for a value of a single type There is at most one singleton and possibly some custom values, indexed by a specific key
Constructors
Cached | |
Fields |
emptyCached :: Cached Source #
An empty cached value (with no cached instances yet)
Type of keys used to cache values A value can either be cached with a specific key, or it is a singleton
cacheAtKey :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Key -> m a -> m a Source #
Make sure that an effectful value is cached after the first evaluation for a specific key
getCached :: (Typeable a, MonadIO m, MonadReader Cache m) => Key -> m (Maybe a) Source #
Get a cached value from the cache This is a IO operation since we access the cache MVar
setCached :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Key -> a -> m () Source #
Cache a value at a given key in the cache This is a IO operation since we access the cache MVar
getCachedValue :: forall a m. (Typeable a, MonadIO m) => Key -> Cache -> m (Maybe a) Source #
Retrieve a cached value given its key
cacheDynValue :: Key -> Dynamic -> Maybe Cached -> Maybe Cached Source #
Insert a (dynamic) value in the Cached data structure for a specific type of value
getDynValue :: Key -> Cached -> Maybe Dynamic Source #
Return the dynamic value cached at a given key
makeTypeText :: forall a. Typeable a => Text Source #
Return a textual description of a Haskell type