registry-0.6.0.0: data structure for assembling components
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Registry.Internal.Cache

Synopsis

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

newtype Cache Source #

A cache for created values, with a map from the textual representation of a type to various cached values

Constructors

Cache (MVar (Map Text Cached)) 

Instances

Instances details
Eq Cache Source # 
Instance details

Defined in Data.Registry.Internal.Cache

Methods

(==) :: Cache -> Cache -> Bool #

(/=) :: Cache -> Cache -> Bool #

MonadReader Cache Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

ask :: Rio Cache #

local :: (Cache -> Cache) -> Rio a -> Rio a #

reader :: (Cache -> a) -> Rio a #

data Cached Source #

Cache for a value of a single type There is at most one singleton and possibly some custom values, indexed by a specific key

Instances

Instances details
Show Cached Source # 
Instance details

Defined in Data.Registry.Internal.Cache

emptyCached :: Cached Source #

An empty cached value (with no cached instances yet)

newCache :: MonadIO m => m Cache Source #

Create an empty cache

askCache :: MonadReader Cache m => m Cache Source #

Get the current cache

data Key Source #

Type of keys used to cache values A value can either be cached with a specific key, or it is a singleton

Constructors

Custom Text 
Singleton 

Instances

Instances details
Show Key Source # 
Instance details

Defined in Data.Registry.Internal.Cache

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key Source # 
Instance details

Defined in Data.Registry.Internal.Cache

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key Source # 
Instance details

Defined in Data.Registry.Internal.Cache

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

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