cauldron-0.6.1.0: Dependency injection library
Safe HaskellNone
LanguageGHC2021

Cauldron

Description

This is a library for performing dependency injection. It's an alternative to manually wiring your functions and passing all required parameters explicitly. Instead of that, you throw your functions into a Cauldron, which wires them for you, guiding itself by the types.

Wiring errors are detected at runtime, not at compile time.

This library should be used at the "composition root" of the application, and only there: the components we are wiring together need not be aware that the library exists.

These extensions, while not required, play well with the library:

{-# LANGUAGE ApplicativeDo #-} -- For building complex values in the Args applicative.
{-# LANGUAGE OverloadedLists #-} -- For avoiding explicit calls to fromRecipeList and fromDecoList

An example of using a Cauldron to wire the constructors of dummy A, B, C datatypes:

>>> :{
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
:}
>>> :{
do
  let cauldron :: Cauldron IO
      cauldron = [
          recipe @A $ val $ wire makeA,
          recipe @B $ val $ wire makeB,
          recipe @C $ eff $ wire makeC -- we use eff because the constructor has IO effects
        ]
  action <- either throwIO pure $ cook forbidDepCycles cauldron
  beans <- action
  pure $ taste @C beans
:}
Just C
Synopsis

Filling the cauldron

data Cauldron (m :: Type -> Type) Source #

A map of bean recipes, indexed by the TypeRep of the bean each recipe ultimately produces. Only one recipe is allowed for each bean type. Parameterized by the monad m in which the recipe Constructors might have effects.

Instances

Instances details
Monoid (Cauldron m) Source # 
Instance details

Defined in Cauldron

Methods

mempty :: Cauldron m #

mappend :: Cauldron m -> Cauldron m -> Cauldron m #

mconcat :: [Cauldron m] -> Cauldron m #

Semigroup (Cauldron m) Source #

Union of two Cauldrons, right-biased: prefers Recipes from the right cauldron when both contain the same key. (Note that Map is left-biased.)

Instance details

Defined in Cauldron

Methods

(<>) :: Cauldron m -> Cauldron m -> Cauldron m #

sconcat :: NonEmpty (Cauldron m) -> Cauldron m #

stimes :: Integral b => b -> Cauldron m -> Cauldron m #

IsList (Cauldron m) Source # 
Instance details

Defined in Cauldron

Associated Types

type Item (Cauldron m) 
Instance details

Defined in Cauldron

type Item (Cauldron m) = SomeRecipe m

Methods

fromList :: [Item (Cauldron m)] -> Cauldron m #

fromListN :: Int -> [Item (Cauldron m)] -> Cauldron m #

toList :: Cauldron m -> [Item (Cauldron m)] #

type Item (Cauldron m) Source # 
Instance details

Defined in Cauldron

type Item (Cauldron m) = SomeRecipe m

empty :: forall (m :: Type -> Type). Cauldron m Source #

insert Source #

Arguments

:: forall {recipelike} {m :: Type -> Type} bean. (Typeable bean, ToRecipe recipelike, HasCallStack) 
=> recipelike m bean

A Recipe or a Constructor.

-> Cauldron m 
-> Cauldron m 

Put a Recipe into the Cauldron.

Only one recipe is allowed for each bean type, so insert for a bean will overwrite any previous recipe for that bean.

adjust :: forall {m :: Type -> Type} bean. Typeable bean => (Recipe m bean -> Recipe m bean) -> Cauldron m -> Cauldron m Source #

Tweak a Recipe inside the Cauldron, if the recipe exists.

delete :: forall (m :: Type -> Type). TypeRep -> Cauldron m -> Cauldron m Source #

keysSet :: forall (m :: Type -> Type). Cauldron m -> Set TypeRep Source #

The set of all TypeRep keys of the map.

restrictKeys :: forall (m :: Type -> Type). Cauldron m -> Set TypeRep -> Cauldron m Source #

Restrict a Cauldron to only those TypeReps found in a Set.

fromRecipeList :: forall (m :: Type -> Type). [SomeRecipe m] -> Cauldron m Source #

toRecipeMap :: forall (m :: Type -> Type). Cauldron m -> Map TypeRep (SomeRecipe m) Source #

hoistCauldron :: (forall x. m x -> n x) -> Cauldron m -> Cauldron n Source #

Change the monad used by the Recipes in the Cauldron.

hoistCauldron' Source #

Arguments

:: (forall x. Typeable x => Args (m (Regs x)) -> Args (n (Regs x)))

Transformation to apply to the base constructor of each recipe.

-> (forall x. Typeable x => Int -> Args (m (Regs x)) -> Args (n (Regs x)))

Transformation to apply to each decorator. Takes the decorator index as parameter.

-> Cauldron m 
-> Cauldron n 

More general form of hoistCauldron that lets you modify the Args inside all the Recipes in the Cauldron. See hoistRecipe'.

Recipes

data Recipe (m :: Type -> Type) bean Source #

Instructions for how to build a value of type bean while possibly performing actions in the monad m.

Because the instructions aren't really run until the Cauldron is cooked, they can be modified with functions like adjust, in order to change the base bean Constructor, or add or remove decorators.

Constructors

Recipe 

Fields

Instances

Instances details
ToRecipe Recipe Source #

Simply identity.

Instance details

Defined in Cauldron

Methods

toRecipe :: forall (m :: Type -> Type) bean. Recipe m bean -> Recipe m bean

class ToRecipe (recipelike :: (Type -> Type) -> Type -> Type) Source #

Convenience typeclass that allows passing either Recipes or Constructors to the insert and recipe functions.

Minimal complete definition

toRecipe

Instances

Instances details
ToRecipe Constructor Source #

Constructor is converted to a Recipe without decorators.

Instance details

Defined in Cauldron

Methods

toRecipe :: forall (m :: Type -> Type) bean. Constructor m bean -> Recipe m bean

ToRecipe Recipe Source #

Simply identity.

Instance details

Defined in Cauldron

Methods

toRecipe :: forall (m :: Type -> Type) bean. Recipe m bean -> Recipe m bean

fromDecoList :: forall (m :: Type -> Type) bean. [Constructor m bean] -> Seq (Constructor m bean) Source #

(|>) :: Seq a -> a -> Seq a infixl 5 #

\( O(1) \). Add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.

(<|) :: a -> Seq a -> Seq a infixr 5 #

\( O(1) \). Add an element to the left end of a sequence. Mnemonic: a triangle with the single element at the pointy end.

hoistRecipe :: (forall x. m x -> n x) -> Recipe m bean -> Recipe n bean Source #

Change the monad used by the bean's main Constructor and its decos.

hoistRecipe' Source #

Arguments

:: (Args (m (Regs bean)) -> Args (n (Regs bean)))

Transformation to apply to the base constructor.

-> (Int -> Args (m (Regs bean)) -> Args (n (Regs bean)))

Transformation to apply to each decorator. Takes the decorator index as parameter.

-> Recipe m bean 
-> Recipe n bean 

More general form of hoistRecipe that enables precise control over the inner Args of each constructor in the Recipe.

How decorators work

Decorators are Constructors which, instead constructing the original version of a bean, they modify it in some way (but without changing its type). Because they modify the bean, typically decorators will take the bean as an argument.

Decorators can have other dependencies beyond the modified bean.

When the bean is a record-of-functions, decorators can be used to add behaviors like caching and logging to the functions.

The order of the decorators in the sequence is the order in which they modify the underlying bean. First decorator wraps first, last decorator wraps last.

>>> :{
newtype Foo = Foo { sayFoo :: IO () }
makeFoo :: Foo
makeFoo = Foo { sayFoo = putStrLn "foo" }
makeFooDeco1 :: Foo -> Foo
makeFooDeco1 Foo { sayFoo } = Foo { sayFoo = putStrLn "deco1 enter" >> sayFoo >> putStrLn "deco1 exit" }
makeFooDeco2 :: Foo -> IO Foo
makeFooDeco2 Foo { sayFoo } = putStrLn "deco2 init" >> pure Foo { sayFoo = putStrLn "deco2 enter" >> sayFoo >> putStrLn "deco2 exit" }
:}
>>> :{
do
  let cauldron :: Cauldron IO
      cauldron = [
          recipe @Foo $ Recipe {
            bean = val $ wire makeFoo,
            decos = [
                 val $ wire makeFooDeco1,
                 eff $ wire makeFooDeco2
              ]
          }
        ]
  action <- either throwIO pure $ cook forbidDepCycles cauldron
  beans <- action
  let Just Foo {sayFoo} = taste beans
  sayFoo
:}
deco2 init
deco2 enter
deco1 enter
foo
deco1 exit
deco2 exit

Hiding a Recipe's bean type

data SomeRecipe (m :: Type -> Type) Source #

In order to put recipes producing different bean types into a container, we need to hide each recipe's bean type. This wrapper allows that.

recipe Source #

Arguments

:: forall {recipelike} {m :: Type -> Type} bean. (ToRecipe recipelike, Typeable bean, HasCallStack) 
=> recipelike m bean

A Recipe or a Constructor.

-> SomeRecipe m 

Build a SomeRecipe from a Recipe or a Constructor. See ToRecipe.

Useful in combination with fromRecipeList.

withRecipe :: forall {m :: Type -> Type} r. (forall bean. Typeable bean => Recipe m bean -> r) -> SomeRecipe m -> r Source #

Access the Recipe inside a SomeRecipe.

getRecipeCallStack :: forall (m :: Type -> Type). SomeRecipe m -> CallStack Source #

For debugging purposes, SomeRecipes remember the CallStack of when they were created.

Constructors

Bean-producing and bean-decorating functions need to be coaxed into Constructors in order to be used in Cauldrons.

data Constructor (m :: Type -> Type) bean Source #

A way of building value of type bean, potentially requiring some dependencies, potentially returning some secondary beans along the primary bean result, and also potentially requiring some initialization effect in a monad m.

Note that only the type of the primary bean is reflected in the Constructor type. Those of the dependencies and secondary beans are not.

A typical initialization monad will be IO, used for example to create mutable references that the bean will use internally. Sometimes the constructor will allocate resources with bracket-like operations, and in that case a monad like Managed might be needed instead.

Instances

Instances details
ToRecipe Constructor Source #

Constructor is converted to a Recipe without decorators.

Instance details

Defined in Cauldron

Methods

toRecipe :: forall (m :: Type -> Type) bean. Constructor m bean -> Recipe m bean

val_ :: forall bean (m :: Type -> Type). (Applicative m, HasCallStack) => Args bean -> Constructor m bean Source #

Create a Constructor from an Args value that returns a bean.

Usually, the Args value will be created by wireing a constructor function.

val :: forall {nested} bean (m :: Type -> Type). (Registrable nested bean, Applicative m, HasCallStack) => Args nested -> Constructor m bean Source #

Like val_, but examines the nested value returned by the Args looking for (potentially nested) tuples. All tuple components except the rightmost-innermost one are registered as secondary beans (if they have Monoid instances, otherwise val won't compile).

val' :: forall bean (m :: Type -> Type). (Applicative m, HasCallStack) => Args (Regs bean) -> Constructor m bean Source #

Like val, but uses an alternative form of registering secondary beans. Less Registrable typeclass magic, but more verbose. Likely not what you want.

eff_ :: forall bean m. (Functor m, HasCallStack) => Args (m bean) -> Constructor m bean Source #

Create a Constructor from an Args value that returns an initialization effect that produces bean.

Usually, the Args value will be created by wireing an effectul constructor function.

ioEff_ :: forall bean (m :: Type -> Type). (MonadIO m, HasCallStack) => Args (IO bean) -> Constructor m bean Source #

Like eff_, but lifts IO constructor effects into a general MonadIO.

eff :: (Registrable nested bean, Monad m, HasCallStack) => Args (m nested) -> Constructor m bean Source #

Like eff_, but examines the nested value produced by the action returned by the Args looking for (potentially nested) tuples. All tuple components except the rightmost-innermost one are registered as secondary beans (if they have Monoid instances, otherwise eff won't compile).

ioEff :: forall {nested} bean (m :: Type -> Type). (Registrable nested bean, MonadIO m, HasCallStack) => Args (IO nested) -> Constructor m bean Source #

Like eff, but lifts IO constructor effects into a general MonadIO.

eff' :: forall bean m. HasCallStack => Args (m (Regs bean)) -> Constructor m bean Source #

Like eff, but uses an alternative form of registering secondary beans. Less Registrable typeclass magic, but more verbose. Likely not what you want.

wire :: Wireable curried tip => curried -> Args tip Source #

Takes a curried function and reads all of its arguments by type using arg, returning an Args for the final result value of the function.

>>> :{
fun0 :: Int
fun0 = 5
w0 :: Args Int
w0 = wire fun0
fun1 :: Bool -> Int
fun1 _ = 5
w1 :: Args Int
w1 = wire fun1
fun2 :: String -> Bool -> Int
fun2 _ _ = 5
w2 :: Args Int
w2 = wire fun2
:}

getConstructorArgs :: Constructor m bean -> Args (m (Regs bean)) Source #

Get the inner Args value for the Constructor, typically for inspecting TypeReps of its arguments/registrations.

getConstructorCallStack :: forall (m :: Type -> Type) bean. Constructor m bean -> CallStack Source #

For debugging purposes, Constructors remember the CallStack of when they were created.

hoistConstructor :: (forall x. m x -> n x) -> Constructor m bean -> Constructor n bean Source #

Change the monad in which the Constructor's effects take place.

hoistConstructor' :: (Args (m (Regs bean)) -> Args (n (Regs bean))) -> Constructor m bean -> Constructor n bean Source #

More general form of hoistConstructor that enables precise control over the inner Args.

Registering secondary beans

There is an exception to the Cauldron rule that each bean type can only be produced by a single Recipe in the Cauldron.

Constructors can produce, besides their "primary" bean result, "secondary" beans that are not reflected in the Constructor signature. Multiple constructors across different Recipes can produce secondary beans of the same type.

Secondary beans are a bit special, in that:

  • The value that is "seen" by a Constructor that depends on a secondary bean is the aggregation of all values produced for that bean in the Cauldron. This means that secondary beans must have Monoid instances, to enable aggregation.
  • When calculating build plan steps for a Cauldron, Constructors that depend on a secondary bean come after all of the Constructors that produce that secondary bean.
  • Secondary beans can't be decorated.
  • A bean type can't be primary and secondary at the same time. See DoubleDutyBeansError.

What are secondary beans useful for?

  • Exposing some uniform control or inspection interface for certain beans.
  • Registering tasks or workers that must be run after application initialization.

The simplest way of registering secondary beans is to pass an Args value returning a tuple to the val (for pure constructors) or eff (for effectful constructors) functions. Components of the tuple other than the rightmost component are considered secondary beans:

>>> :{
con :: Constructor Identity String
con = val $ pure (Sum @Int, All False, "foo")
effCon :: Constructor IO String
effCon = eff $ pure $ pure @IO (Sum @Int, All False, "foo")
:}

Example of how secondary bean values are accumulated:

>>> :{
data U = U deriving Show
data V = V deriving Show
makeU :: (Sum Int, U)
makeU = (Sum 1, U)
makeV :: U -> (Sum Int, V)
makeV = \_ -> (Sum 7, V)
newtype W = W (Sum Int) deriving Show -- depends on the secondary bean
:}
>>> :{
do
  let cauldron :: Cauldron Identity
      cauldron = [
          recipe @U $ val $ wire makeU,
          recipe @V $ val $ wire makeV,
          recipe @W $ val $ wire W
        ]
  Identity beans <- either throwIO pure $ cook forbidDepCycles cauldron
  pure $ taste @W beans
:}
Just (W (Sum {getSum = 8}))

Cooking the beans

cook :: Monad m => Fire m -> Cauldron m -> Either RecipeError (m Beans) Source #

Build the beans using the recipeMap stored in the Cauldron.

Any secondary beans that are registered by constructors are aggregated monoidally.

cookNonEmpty :: Monad m => NonEmpty (Fire m, Cauldron m) -> Either RecipeError (m (NonEmpty Beans)) Source #

Cook a nonempty list of Cauldrons.

Cauldrons later in the list can see the beans in all previous Cauldrons, but not vice versa.

Beans in a Cauldron have priority over the same beans in previous Cauldrons.

cookTree :: Monad m => Tree (Fire m, Cauldron m) -> Either RecipeError (m (Tree Beans)) Source #

Cook a hierarchy of Cauldrons.

Cauldrons down in the branches can see the beans of their ancestor Cauldrons, but not vice versa.

Beans in a Cauldron have priority over the same beans in ancestor Cauldrons.

How loopy can we get?

data Fire (m :: Type -> Type) Source #

Strategy for dealing with dependency cycles.

(The name is admittedly uninformative; the culinary metaphor was stretched too far.)

forbidDepCycles :: forall (m :: Type -> Type). Monad m => Fire m Source #

Forbid any kind of cyclic dependencies between beans. This is probably what you want.

allowSelfDeps :: forall (m :: Type -> Type). MonadFix m => Fire m Source #

Allow direct self-dependencies.

A bean constructor might depend on itself. This can be useful for having decorated self-invocations, because the version of the bean received as argument comes "from the future" and is already decorated.

Note that a MonadFix instance is required of the initialization monad.

BEWARE: Pattern-matching too eagerly on a "bean from the future" during construction will cause infinite loops or, if you are lucky, throw FixIOExceptions.

allowDepCycles :: forall (m :: Type -> Type). MonadFix m => Fire m Source #

Allow any kind of dependency cycles.

Usually comes in handy for creating serializers / deserializers for mutually dependent types.

Note that a MonadFix instance is required of the initialization monad.

BEWARE: Pattern-matching too eagerly on argument beans during construction will cause infinite loops or, if you are lucky, throw FixIOExceptions.

Tasting the results

data Beans Source #

A map of Dynamic values, indexed by the TypeRep of each Dynamic. Maintains the invariant that the TypeRep of the key matches the TypeRep of the Dynamic.

Instances

Instances details
Monoid Beans Source # 
Instance details

Defined in Cauldron.Beans

Methods

mempty :: Beans #

mappend :: Beans -> Beans -> Beans #

mconcat :: [Beans] -> Beans #

Semigroup Beans Source #

Union of two Beans maps, right-biased: prefers values from the right Beans map when both contain the same TypeRep key. (Note that Map is left-biased.)

Instance details

Defined in Cauldron.Beans

Methods

(<>) :: Beans -> Beans -> Beans #

sconcat :: NonEmpty Beans -> Beans #

stimes :: Integral b => b -> Beans -> Beans #

IsList Beans Source # 
Instance details

Defined in Cauldron.Beans

Associated Types

type Item Beans 
Instance details

Defined in Cauldron.Beans

Show Beans Source # 
Instance details

Defined in Cauldron.Beans

Methods

showsPrec :: Int -> Beans -> ShowS #

show :: Beans -> String #

showList :: [Beans] -> ShowS #

type Item Beans Source # 
Instance details

Defined in Cauldron.Beans

taste :: Typeable bean => Beans -> Maybe bean Source #

Check if the Beans map contains a value of type bean.

When things go wrong

data RecipeError Source #

Sometimes the cooking process goes wrong.

Constructors

MissingDependenciesError MissingDependencies

A Constructor depends on beans that can't be found either in the current Cauldron or its ancestors.

DoubleDutyBeansError DoubleDutyBeans

Beans that work both as primary beans and as secondary beans are disallowed.

DependencyCycleError DependencyCycle

Dependency cycles are disallowed by some Fires.

newtype DoubleDutyBeans Source #

Instances

Instances details
Show DoubleDutyBeans Source # 
Instance details

Defined in Cauldron

Visualizing dependencies between beans.

getDependencyGraph :: forall (m :: Type -> Type). Cauldron m -> DependencyGraph Source #

Get a graph of dependencies between BeanConstructionSteps. The graph can be obtained even if the Cauldron can't be cooked successfully.

defaultStyle :: Maybe RecipeError -> Style BeanConstructionStep Text Source #

Default DOT rendering style to use with writeAsDot. When a RecipeError exists, is highlights the problematic BeanConstructionSteps.

data BeanConstructionStep Source #

A step in the construction of a bean value.

Constructors

BarePrimaryBean TypeRep

Undecorated bean.

PrimaryBeanDeco TypeRep Int

Apply the decorator with the given index. Comes after the BarePrimaryBean and all PrimaryBeanDecos with a lower index value.

PrimaryBean TypeRep

Final, fully decorated version of a bean. If there are no decorators, comes directly after BarePrimaryBean.

SecondaryBean TypeRep

Beans that are secondary registrations of a Constructor and which are aggregated monoidally.

toAdjacencyMap :: DependencyGraph -> AdjacencyMap BeanConstructionStep Source #

Conversion to a graph type from the algebraic-graphs library for further processing.

Simplifying the dep graph

DependencyGraphs can get complex and difficult to intepret because they include bean decorators and secondary beans, details in which we many not be interested.

These functions help simplify DependencyGraphs before passing them to writeAsDot. They can be composed between themselves.

removeSecondaryBeans :: DependencyGraph -> DependencyGraph Source #

Remove all vertices and edges related to secondary beans.

removeDecos :: DependencyGraph -> DependencyGraph Source #

Remove all vertices and edges related to bean decorators.

collapseToPrimaryBeans :: DependencyGraph -> DependencyGraph Source #

Unifies PrimaryBeans with their respective BarePrimaryBeans and PrimaryBeanDecos.

Also removes any self-loops.