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

Data.Registry.Rio

Description

Utilities for working with resources

Synopsis

Documentation

class MakeSingletons ls where Source #

This typeclass take an existing registry and makes a singleton for each Rio output type

Methods

makeSingletons :: SingletonsRegistry ls ins out -> SingletonsRegistry '[] ins out Source #

Instances

Instances details
MakeSingletons ('[] :: [Type]) Source #

If the list of types is empty there is nothing to do

Instance details

Defined in Data.Registry.Rio

Methods

makeSingletons :: forall (ins :: [Type]) (out :: [Type]). SingletonsRegistry '[] ins out -> SingletonsRegistry '[] ins out Source #

(Typeable a, MakeSingletons rest) => MakeSingletons (Rio a ': rest) Source #

If the type represents an effectful value, make a singleton for it and recurse on the rest

Instance details

Defined in Data.Registry.Rio

Methods

makeSingletons :: forall (ins :: [Type]) (out :: [Type]). SingletonsRegistry (Rio a ': rest) ins out -> SingletonsRegistry '[] ins out Source #

MakeSingletons rest => MakeSingletons (a ': rest) Source #

If the type represents a pure value, make singletons for the rest

Instance details

Defined in Data.Registry.Rio

Methods

makeSingletons :: forall (ins :: [Type]) (out :: [Type]). SingletonsRegistry (a ': rest) ins out -> SingletonsRegistry '[] ins out Source #

newtype SingletonsRegistry (todo :: [Type]) (ins :: [Type]) (out :: [Type]) Source #

Registry where all Rio values are singletons

Constructors

SingletonsRegistry 

Fields

newtype Rio a Source #

This data type provides some support for creating effectful components with resources You can use the regular MonadResource functions like allocate to make sure that resources are cleaned up You can also use the cacheAt function

Constructors

Rio 

Instances

Instances details
MonadIO Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

liftIO :: IO a -> Rio a #

Applicative Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

pure :: a -> Rio a #

(<*>) :: Rio (a -> b) -> Rio a -> Rio b #

liftA2 :: (a -> b -> c) -> Rio a -> Rio b -> Rio c #

(*>) :: Rio a -> Rio b -> Rio b #

(<*) :: Rio a -> Rio b -> Rio a #

Functor Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

fmap :: (a -> b) -> Rio a -> Rio b #

(<$) :: a -> Rio b -> Rio a #

Monad Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

(>>=) :: Rio a -> (a -> Rio b) -> Rio b #

(>>) :: Rio a -> Rio b -> Rio b #

return :: a -> Rio a #

MonadResource Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

liftResourceT :: ResourceT IO a -> Rio a #

MonadUnliftIO Rio Source # 
Instance details

Defined in Data.Registry.Rio

Methods

withRunInIO :: ((forall a. Rio a -> IO a) -> IO b) -> Rio b #

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 #

(Typeable a, MakeSingletons rest) => MakeSingletons (Rio a ': rest) Source #

If the type represents an effectful value, make a singleton for it and recurse on the rest

Instance details

Defined in Data.Registry.Rio

Methods

makeSingletons :: forall (ins :: [Type]) (out :: [Type]). SingletonsRegistry (Rio a ': rest) ins out -> SingletonsRegistry '[] ins out Source #

runRio :: MonadIO m => Rio a -> m a Source #

Run a Rio action by providing an empty cache and allocating / destroying resources

execRio :: MonadIO m => Rio a -> m (a, Cache) Source #

Run a Rio action by providing an empty cache and allocating / destroying resources

withRio :: MonadIO m => Rio a -> (a -> IO b) -> m b Source #

Use the value created by a Rio action so that resources are properly allocated and cached

withRioM :: (MonadResource (m (ResourceT IO)), MFunctor m) => Rio a -> (a -> m IO b) -> m IO b Source #

Use the value created by a Rio action so that resources are properly allocated and cached inside a monad transformer

runCache :: Rio a -> ResourceT IO a Source #

Run a Rio action by providing an empty cache

execCache :: Rio a -> ResourceT IO (a, Cache) Source #

Run a Rio action by providing an empty cache, and return the final cache for inspection

liftRio :: ResourceT IO a -> Rio a Source #

Lift a resourceful value into Rio

withRegistry :: forall a b ins out m. (Typeable a, MonadIO m, MakeSingletons out) => Registry ins out -> (a -> IO b) -> m b Source #

This function must be used to run services involving resources The value a is created using the registry, used with the function f and all resources are freed at the end

withRegistryM :: forall a b ins out m. (Typeable a, MonadResource (m (ResourceT IO)), MFunctor m, MakeSingletons out) => Registry ins out -> (a -> m IO b) -> m IO b Source #

This function works like withRegistry for a higher-order monad, typically `PropertyT IO` when writing property tests with Hedgehog

runRegistryT :: forall a ins out. (Typeable a, MakeSingletons out) => Registry ins out -> ResourceT IO a Source #

Create a function of type a with a given registry Return a ResourceT value to control resource allocation

singletons :: forall ins out. MakeSingletons out => Registry ins out -> Registry ins out Source #

Make singletons for all the output types of a registry but only if they not specialized values

startSingletonsRegistry :: Registry ins out -> SingletonsRegistry out ins out Source #

Prepare a Registry for making singletons

makeSingletonsRegistry :: forall todo ins out. Registry ins out -> SingletonsRegistry todo ins out Source #

Prepare a Registry for making singletons on a specific list of types

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

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