registry-0.1.5.1: data structure for assembling components

Safe HaskellNone
LanguageHaskell2010

Data.Registry.RIO

Contents

Description

RIO is equivalent to ResourceT (WriterT Warmup IO) It can be used to instantiate "components as records of functions" where each component can allocate resources and have a "warmup phase" to preload data or assess if it is working properly.

Synopsis

Documentation

newtype Stop Source #

Data type encapsulating resource finalizers

Constructors

Stop InternalState 

runStop :: Stop -> IO () Source #

Run all finalizers

newtype RIO a Source #

This newtype creates a monad to sequence component creation actions, cumulating start/stop tasks found along the way

Constructors

RIO 

Fields

Instances
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 #

fail :: String -> 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 #

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 #

MonadIO RIO Source # 
Instance details

Defined in Data.Registry.RIO

Methods

liftIO :: IO a -> RIO a #

Alternative RIO Source # 
Instance details

Defined in Data.Registry.RIO

Methods

empty :: RIO a #

(<|>) :: RIO a -> RIO a -> RIO a #

some :: RIO a -> RIO [a] #

many :: RIO a -> RIO [a] #

MonadThrow RIO Source # 
Instance details

Defined in Data.Registry.RIO

Methods

throwM :: Exception e => e -> RIO a #

MonadResource RIO Source # 
Instance details

Defined in Data.Registry.RIO

Methods

liftResourceT :: ResourceT IO a -> RIO a #

Alt RIO Source # 
Instance details

Defined in Data.Registry.RIO

Methods

(<!>) :: RIO a -> RIO a -> RIO a #

some :: Applicative RIO => RIO a -> RIO [a] #

many :: Applicative RIO => RIO a -> RIO [a] #

MonadBase IO RIO Source # 
Instance details

Defined in Data.Registry.RIO

Methods

liftBase :: IO α -> RIO α #

For production

withRIO :: MonadIO m => RIO a -> (a -> IO ()) -> m Result Source #

Use a RIO value and make sure that resources are closed Only run the action if the warmup is successful

withRegistry :: forall a b ins out m. (Typeable a, Contains (RIO a) out, Solvable ins out, MonadIO m, MemoizedActions out) => Registry ins out -> (Result -> a -> IO b) -> m b Source #

This function must be used to run services involving a top component It creates the top component and invokes all warmup functions

The passed function f is used to decide whether to continue or not depending on the Result

We also make sure that all effects are memoized by calling memoizeAll on the Registry here!

runRegistryT :: forall a ins out m. (Typeable a, Contains (RIO a) out, Solvable ins out, MonadIO m, MemoizedActions out) => Registry ins out -> ResourceT m (a, Warmup) Source #

This can be used if you want to insert the component creation inside another action managed with ResourceT. Or if you want to call runResourceT yourself later

For testing

unsafeRunRIO :: (Typeable a, MonadIO m) => RIO a -> m a Source #

This runs a RIO value without closing down resources or executing startup actions

withNoWarmupRIO :: MonadIO m => RIO a -> (a -> IO b) -> m b Source #

Use a RIO value and make sure that resources are closed Don't run the warmup

withRIOIgnoreWarmupResult :: MonadIO m => RIO a -> (a -> IO b) -> m b Source #

Use a RIO value and make sure that resources are closed Run the warmup but ignore the result

withRIOAndWarmupResult :: MonadIO m => (Result -> IO ()) -> RIO a -> (a -> IO b) -> m b Source #

Use a RIO value and make sure that resources are closed Run a unit function with the warmup result (print or throw exception)

executeRegistry :: forall a ins out m. (Typeable a, Contains (RIO a) out, Solvable ins out, MonadIO m) => Registry ins out -> m (a, Warmup, Stop) Source #

Instantiate the component but don't execute the warmup (it may take time) and keep the Stop value to clean resources later This function statically checks that the component can be instantiated

unsafeRun :: forall a ins out m. (Typeable a, Contains (RIO a) out, MonadIO m) => Registry ins out -> m a Source #

Instantiate the component but don't execute the warmup (it may take time) and lose a way to cleanu up resources | Almost no compilation time is spent on checking that component resolution is possible

unsafeRunDynamic :: forall a ins out m. (Typeable a, MonadIO m) => Registry ins out -> m a Source #

Instantiate the component but don't execute the warmup (it may take time) and lose a way to cleanu up resources Don't even check that a component can be built out of the registry

unsafeRunWithStop :: forall a ins out m. (Typeable a, Contains (RIO a) out, MonadIO m) => Registry ins out -> m (a, Stop) Source #

Same as unsafeRun but keep the Stop value to be able to clean resources later

unsafeRunDynamicWithStop :: forall a ins out m. (Typeable a, MonadIO m) => Registry ins out -> m (a, Stop) Source #

warmupWith :: Warmup -> RIO () Source #

Lift a Warmup action into the RIO monad

allocate :: IO a -> (a -> IO ()) -> RIO a Source #

Allocate some resource