Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Data.Registry.Rio
Description
Utilities for working with resources
Synopsis
- newtype Rio a = Rio {}
- class MakeSingletons ls where
- makeSingletons :: SingletonsRegistry ls ins out -> SingletonsRegistry '[] ins out
- newtype SingletonsRegistry (todo :: [Type]) (ins :: [Type]) (out :: [Type]) = SingletonsRegistry {
- _singletonsRegistry :: Registry ins out
- runRio :: MonadIO m => Rio a -> m a
- runCache :: Rio a -> ResourceT IO a
- execRio :: MonadIO m => Rio a -> m (a, Cache)
- execCache :: Rio a -> ResourceT IO (a, Cache)
- withRio :: MonadIO m => Rio a -> (a -> IO b) -> m b
- withRioM :: (MonadResource (m (ResourceT IO)), MFunctor m) => Rio a -> (a -> m IO b) -> m IO b
- liftRio :: ResourceT IO a -> Rio a
- withRegistry :: forall a b ins out m. (Typeable a, MonadIO m, MakeSingletons out) => Registry ins out -> (a -> IO b) -> m b
- runRegistryT :: forall a ins out. (Typeable a, MakeSingletons out) => Registry ins out -> ResourceT IO a
- 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
- singletons :: forall ins out. MakeSingletons out => Registry ins out -> Registry ins out
- startSingletonsRegistry :: Registry ins out -> SingletonsRegistry out ins out
- makeSingletonsRegistry :: forall todo ins out. Registry ins out -> SingletonsRegistry todo ins out
- singleton :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => m a -> m a
- cacheAt :: forall a m. (Typeable a, MonadIO m, MonadReader Cache m) => Text -> m a -> m a
Documentation
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
Instances
MonadIO Rio Source # | |
Defined in Data.Registry.Rio | |
Applicative Rio Source # | |
Functor Rio Source # | |
Monad Rio Source # | |
MonadResource Rio Source # | |
Defined in Data.Registry.Rio Methods liftResourceT :: ResourceT IO a -> Rio a # | |
MonadUnliftIO Rio Source # | |
Defined in Data.Registry.Rio | |
MonadReader Cache Rio 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 |
Defined in Data.Registry.Rio Methods makeSingletons :: forall (ins :: [Type]) (out :: [Type]). SingletonsRegistry (Rio a ': rest) ins out -> SingletonsRegistry '[] ins out Source # |
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
MakeSingletons ('[] :: [Type]) Source # | If the list of types is empty there is nothing to do |
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 |
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 |
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
|
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
execCache :: Rio a -> ResourceT IO (a, Cache) Source #
Run a Rio action by providing an empty cache, and return the final cache for inspection
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
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
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
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
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