| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Cauldron.Builder
Description
This module is not required to use Cauldrons, but it provides a Builder monad which lets you
define them in a manner which more closely resembles the syntax of wiring things "manually" in IO or Managed.
>>>:{data Foo = EndFoo | FooToBar Bar deriving stock (Show) -- data Bar = EndBar | BarToFoo Foo deriving stock (Show) -- newtype Serializer a = Serializer {runSerializer :: a -> String} -- makeFooSerializer :: Serializer Bar -> Serializer Foo makeFooSerializer Serializer {runSerializer = runBar} = Serializer { runSerializer = \case EndFoo -> ".EndFoo" FooToBar bar -> ".FooToBar" ++ runBar bar } -- makeBarSerializer :: Serializer Foo -> Serializer Bar makeBarSerializer Serializer {runSerializer = runFoo} = Serializer { runSerializer = \case EndBar -> ".EndBar" BarToFoo foo -> ".BarToFoo" ++ runFoo foo } -- builder :: Builder Identity () builder = mdo foo <- _val_ $ makeFooSerializer <$> bar bar <- _val_ $ makeBarSerializer <$> foo pure () -- cauldron :: Either DuplicateBeans (Cauldron Identity) cauldron = execBuilder builder :}
Note that in the Builder monad the values that we bind with <- when using
functions like add, _val_, or _eff_ are really Args values which
merely carry type information. We can dispense with them and use arg or
wire instead:
>>>:{builder2 :: Builder Identity () builder2 = mdo _ <- add $ val_ $ makeFooSerializer <$> arg _ <- _val_ $ wire makeBarSerializer pure () :}
Synopsis
- data Builder (m :: Type -> Type) a
- add :: forall {recipelike} {m :: Type -> Type} bean. (Typeable bean, ToRecipe recipelike, HasCallStack) => recipelike m bean -> Builder m (Args bean)
- execBuilder :: forall (m :: Type -> Type) a. Builder m a -> Either DuplicateBeans (Cauldron m)
- data DuplicateBeans = DuplicateBeans (Map TypeRep (CallStack, CallStack, [CallStack]))
- prettyDuplicateBeans :: DuplicateBeans -> String
- prettyDuplicateBeansLines :: DuplicateBeans -> [String]
- class (Monad m, Applicative (ArgsApplicative m), Monad (ConstructorMonad m)) => MonadWiring (m :: Type -> Type) where
- type ArgsApplicative (m :: Type -> Type) :: Type -> Type
- type ConstructorMonad (m :: Type -> Type) :: Type -> Type
- _val_ :: (Typeable bean, HasCallStack) => ArgsApplicative m bean -> m (ArgsApplicative m bean)
- _eff_ :: (Typeable bean, HasCallStack) => ArgsApplicative m (ConstructorMonad m bean) -> m (ArgsApplicative m bean)
- _ioEff_ :: (MonadWiring m, MonadIO (ConstructorMonad m), Typeable bean, HasCallStack) => ArgsApplicative m (IO bean) -> m (ArgsApplicative m bean)
Documentation
data Builder (m :: Type -> Type) a Source #
Instances
| Monad m => MonadWiring (Builder m) Source # | |||||||||
Defined in Cauldron.Builder Associated Types
Methods _val_ :: (Typeable bean, HasCallStack) => ArgsApplicative (Builder m) bean -> Builder m (ArgsApplicative (Builder m) bean) Source # _eff_ :: (Typeable bean, HasCallStack) => ArgsApplicative (Builder m) (ConstructorMonad (Builder m) bean) -> Builder m (ArgsApplicative (Builder m) bean) Source # | |||||||||
| Applicative (Builder m) Source # | |||||||||
| Functor (Builder m) Source # | |||||||||
| Monad (Builder m) Source # | |||||||||
| MonadFix (Builder m) Source # | |||||||||
Defined in Cauldron.Builder | |||||||||
| type ArgsApplicative (Builder m) Source # | |||||||||
Defined in Cauldron.Builder | |||||||||
| type ConstructorMonad (Builder m) Source # | |||||||||
Defined in Cauldron.Builder | |||||||||
Arguments
| :: forall {recipelike} {m :: Type -> Type} bean. (Typeable bean, ToRecipe recipelike, HasCallStack) | |
| => recipelike m bean | A |
| -> Builder m (Args bean) |
execBuilder :: forall (m :: Type -> Type) a. Builder m a -> Either DuplicateBeans (Cauldron m) Source #
Two beans of the same type are forbidden
data DuplicateBeans Source #
Because cauldron inject dependencies based on their types, a do-notation block which binds two or more values of the same type would be ambiguous.
>>>:{builderOops :: Builder Identity () builderOops = do foo1 <- _val_ $ pure (5 :: Int) foo2 <- _val_ $ pure (6 :: Int) pure () :}
>>>:{case execBuilder builderOops of Left (DuplicateBeans _) -> "this should be the result" Right _ -> "won't happen" :} "this should be the result"
Instances
| Exception DuplicateBeans Source # | |
Defined in Cauldron.Builder Methods toException :: DuplicateBeans -> SomeException # fromException :: SomeException -> Maybe DuplicateBeans # displayException :: DuplicateBeans -> String # backtraceDesired :: DuplicateBeans -> Bool # | |
| Show DuplicateBeans Source # | |
Defined in Cauldron.Builder Methods showsPrec :: Int -> DuplicateBeans -> ShowS # show :: DuplicateBeans -> String # showList :: [DuplicateBeans] -> ShowS # | |
Being polymorphic on the wiring monad
class (Monad m, Applicative (ArgsApplicative m), Monad (ConstructorMonad m)) => MonadWiring (m :: Type -> Type) where Source #
This class allows you to define polymorphic "wirings" which can work in
the Builder monad to produce Cauldrons, but also wire beans directly in
IO or Managed.
If we limit ourselves exclusively to the methods of this class, it's not possible to define decorators or secondary beans.
This class can help migrating from "direct"-style wirings to Cauldrons.
>>>:{data A = A deriving Show data B = B deriving Show data C = C deriving Show makeA :: A makeA = A makeB :: A -> B makeB = \_ -> B makeC :: A -> B -> IO C makeC = \_ _ -> pure C instantiations :: (Builder IO (Args C), IO (Identity C)) instantiations = let polymorphicWiring = do a <- _val_ $ pure makeA b <- _val_ $ makeB <$> a c <- _ioEff_ $ makeC <$> a <*> b pure c in (polymorphicWiring, polymorphicWiring) :}
Associated Types
type ArgsApplicative (m :: Type -> Type) :: Type -> Type Source #
Wraps every bean type that we bind using methods of this class.
Will be Args for Builder, but simply Identity for IO and Managed.
type ConstructorMonad (m :: Type -> Type) :: Type -> Type Source #
The monad in which constructors have effects.
Methods
_val_ :: (Typeable bean, HasCallStack) => ArgsApplicative m bean -> m (ArgsApplicative m bean) Source #
_eff_ :: (Typeable bean, HasCallStack) => ArgsApplicative m (ConstructorMonad m bean) -> m (ArgsApplicative m bean) Source #
Instances
_ioEff_ :: (MonadWiring m, MonadIO (ConstructorMonad m), Typeable bean, HasCallStack) => ArgsApplicative m (IO bean) -> m (ArgsApplicative m bean) Source #