module Data.Registry.RIO where

import Control.Monad.Trans.Resource
import Data.Registry.Make
import Data.Registry.Registry
import Data.Registry.Solver
import Protolude

type RIO = ResourceT IO

-- | 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!
withRegistry ::
  forall a b ins out m.
  (Typeable a, Contains (RIO a) out, Solvable ins out, MonadIO m, MemoizedActions out) =>
  Registry ins out ->
  (a -> IO b) ->
  m b
withRegistry :: forall a b (ins :: [*]) (out :: [*]) (m :: * -> *).
(Typeable a, Contains (RIO a) out, Solvable ins out, MonadIO m,
 MemoizedActions out) =>
Registry ins out -> (a -> IO b) -> m b
withRegistry Registry ins out
registry a -> IO b
f = IO b -> m b
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO b -> m b) -> IO b -> m b
forall a b. (a -> b) -> a -> b
$
  ResourceT IO b -> IO b
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT (forall a (ins :: [*]) (out :: [*]).
(Typeable a, Contains (RIO a) out, Solvable ins out,
 MemoizedActions out) =>
Registry ins out -> RIO a
runRegistryT @a Registry ins out
registry RIO a -> (a -> ResourceT IO b) -> ResourceT IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO b -> ResourceT IO b
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO b -> ResourceT IO b) -> (a -> IO b) -> a -> ResourceT IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO b
f)

-- | 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
runRegistryT ::
  forall a ins out .
  (Typeable a, Contains (RIO a) out, Solvable ins out, MemoizedActions out) =>
  Registry ins out ->
  ResourceT IO a
runRegistryT :: forall a (ins :: [*]) (out :: [*]).
(Typeable a, Contains (RIO a) out, Solvable ins out,
 MemoizedActions out) =>
Registry ins out -> RIO a
runRegistryT Registry ins out
registry =
  IO (Registry ins out) -> ResourceT IO (Registry ins out)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall (m :: * -> *) (ins :: [*]) (out :: [*]).
(MonadIO m, MemoizedActions out) =>
Registry ins out -> IO (Registry ins out)
memoizeAll @RIO Registry ins out
registry) ResourceT IO (Registry ins out)
-> (Registry ins out -> RIO a) -> RIO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a (ins :: [*]) (out :: [*]).
Typeable a =>
Registry ins out -> a
make @(RIO a)