cauldron-0.4.0.0: Toy dependency injection framework
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.

>>> :{
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 =
        emptyCauldron
        & insert @A do makeBean do pack value makeA
        & insert @B do makeBean do pack value makeB
        & insert @C do makeBean do pack effect makeC
      Right (_ :: DependencyGraph, action) = cook forbidDepCycles cauldron
  beans <- action
  pure do taste @C beans
:}
Just C
Synopsis

Filling the cauldron

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

A map of Bean recipes. Parameterized by the monad m in which the Bean 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 values from the right cauldron when both contain the same bean. (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 #

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

insert :: forall bean (m :: Type -> Type). Typeable bean => Bean m bean -> Cauldron m -> Cauldron m Source #

Put a recipe for a Bean into the Cauldron.

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

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

Tweak an already existing Bean recipe.

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

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

Change the monad used by the beans in the Cauldron.

Beans

data Bean (m :: Type -> Type) bean where Source #

A bean recipe, to be inserted into a Cauldron.

Constructors

Bean 

Fields

  • :: forall (m :: Type -> Type) bean. { constructor :: Constructor m bean

    How to build the bean itself.

  •    , decos :: Decos m bean

    How to build the decorators that wrap the bean. There might be no decorators.

  •    } -> Bean m bean
     

makeBean :: forall (m :: Type -> Type) a. Constructor m a -> Bean m a Source #

A Bean without decorators, having only the main constructor.

setConstructor :: forall (m :: Type -> Type) bean. Constructor m bean -> Bean m bean -> Bean m bean Source #

setDecos :: forall (m :: Type -> Type) bean. Decos m bean -> Bean m bean -> Bean m bean Source #

overDecos :: forall (m :: Type -> Type) bean. (Decos m bean -> Decos m bean) -> Bean m bean -> Bean m bean Source #

hoistBean :: (forall x. m x -> n x) -> Bean m bean -> Bean n bean Source #

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

Decorators

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, logging... to the functions.

>>> :{
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 =
        emptyCauldron
        & insert @Foo
          Bean {
            constructor = pack value makeFoo,
            decos = fromConstructors [
                 pack value makeFooDeco1,
                 pack effect makeFooDeco2
              ]
          }
      Right (_ :: DependencyGraph, action) = cook forbidDepCycles cauldron
  beans <- action
  let Just Foo {sayFoo} = taste beans
  sayFoo
:}
deco2 init
deco2 enter
deco1 enter
foo
deco1 exit
deco2 exit

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

A list of Constructors for the decorators of some Bean.

Constructors for a decorator will have the bean itself among their arguments. That bean argument will be either the "bare" undecorated bean (for the first decorator) or the result of applying the previous decorator in the list.

Decorators can have other dependencies besides the bean.

Instances

Instances details
Monoid (Decos m bean) Source # 
Instance details

Defined in Cauldron

Methods

mempty :: Decos m bean #

mappend :: Decos m bean -> Decos m bean -> Decos m bean #

mconcat :: [Decos m bean] -> Decos m bean #

Semigroup (Decos m bean) Source # 
Instance details

Defined in Cauldron

Methods

(<>) :: Decos m bean -> Decos m bean -> Decos m bean #

sconcat :: NonEmpty (Decos m bean) -> Decos m bean #

stimes :: Integral b => b -> Decos m bean -> Decos m bean #

IsList (Decos m bean) Source # 
Instance details

Defined in Cauldron

Associated Types

type Item (Decos m bean) 
Instance details

Defined in Cauldron

type Item (Decos m bean) = Constructor m bean

Methods

fromList :: [Item (Decos m bean)] -> Decos m bean #

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

toList :: Decos m bean -> [Item (Decos m bean)] #

type Item (Decos m bean) Source # 
Instance details

Defined in Cauldron

type Item (Decos m bean) = Constructor m bean

emptyDecos :: forall (m :: Type -> Type) bean. Decos m bean Source #

Empty list of decorators.

fromConstructors :: forall (m :: Type -> Type) bean. [Constructor m bean] -> Decos m bean Source #

Build the decorators from a list of Constructors, first innermost, last outermost.

addOuter :: forall (m :: Type -> Type) bean. Constructor m bean -> Decos m bean -> Decos m bean Source #

Add a new decorator that modifies the bean after all existing decorators.

This means the behaviours it adds to the bean's methods will be applied first when entering the method.

addInner :: forall (m :: Type -> Type) bean. Constructor m bean -> Decos m bean -> Decos m bean Source #

Add a new decorator that modifies the bean before all existing decorators.

This means the behaviours it adds to the bean's methods will be applied last, just before entering the base bean's method.

Usually addOuter is preferrable.

hoistDecos :: (forall x. m x -> n x) -> Decos m bean -> Decos n bean Source #

Change the monad used by the decorators.

Constructors

The bean-producing or bean-decorating functions that we want to wire need to be coaxed into a Constructor value before creating a Bean recipe and adding it to the Cauldron.

If your aren't dealing with secondary beans, don't sweat it: use pack value for pure constructors functions and pack effect for effectful ones. That should be enough.

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

A way of building some bean value, 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 a constructor will allocate resources with bracket-like operations, and in that case a monad like Managed might be needed instead.

pack Source #

Arguments

:: forall (args :: [Type]) r curried (regs :: [Type]) bean (m :: Type -> Type). (MulticurryableF args r curried (IsFunction curried), All (Typeable :: Type -> Constraint) args, All (And (Typeable :: Type -> Constraint) Monoid) regs) 
=> Packer m regs bean r

Fit the outputs of the constructor into the auxiliary Regs type.

See regs1 and similar functions.

-> curried

Action returning a function ending in r, some datatype containing regs and bean values.

-> Constructor m bean 

Take a curried function that constructs a bean, uncurry it recursively and then apply a Packer to its tip, resulting in a Constructor.

>>> :{
data A = A deriving Show
data B = B deriving Show
data C = C deriving Show
makeB :: A -> B
makeB = \_ -> B
makeC :: A -> B -> IO C
makeC = \_ _ -> pure C
constructorB :: Constructor IO B
constructorB = pack value makeB
constructorC :: Constructor IO C
constructorC = pack effect makeC
:}

There are pack0, pack1... functions which work for specific number of arguments, but the generic pack should work in most cases anyway.

pack0 Source #

Arguments

:: forall (regs :: [Type]) (m :: Type -> Type) bean r. All (And (Typeable :: Type -> Constraint) Monoid) regs 
=> Packer m regs bean r 
-> r

0-argument constructor

-> Constructor m bean 

Slightly simpler version of pack for 0-argument functions.

pack1 Source #

Arguments

:: forall arg1 r (m :: Type -> Type) (regs :: [Type]) bean. (Typeable arg1, All (And (Typeable :: Type -> Constraint) Monoid) regs) 
=> Packer m regs bean r 
-> (arg1 -> r)

1-argument constructor

-> Constructor m bean 

Slightly simpler version of pack for 1-argument functions.

pack2 Source #

Arguments

:: forall arg1 arg2 r (m :: Type -> Type) (regs :: [Type]) bean. (Typeable arg1, Typeable arg2, All (And (Typeable :: Type -> Constraint) Monoid) regs) 
=> Packer m regs bean r 
-> (arg1 -> arg2 -> r)

2-argument constructor

-> Constructor m bean 

Slightly simpler version of pack for 2-argument functions.

pack3 Source #

Arguments

:: forall arg1 arg2 arg3 r (m :: Type -> Type) (regs :: [Type]) bean. (Typeable arg1, Typeable arg2, Typeable arg3, All (And (Typeable :: Type -> Constraint) Monoid) regs) 
=> Packer m regs bean r 
-> (arg1 -> arg2 -> arg3 -> r)

3-argument constructor

-> Constructor m bean 

Slightly simpler version of pack for 3-argument functions.

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.

newtype Packer (m :: Type -> Type) (regs :: [Type]) bean r Source #

Applies a transformation to the tip of a curried function, coaxing it into the shape expected by a Constructor, which includes information about which is the primary bean and which are the secondary ones.

  • For pure constructors without registrations, try value.
  • For effectful constructors without registrations, try effect.

More complex cases might require valueWith, effectWith, or working with the Packer constructor itself.

Constructors

Packer (r -> m (Regs regs bean)) 

Instances

Instances details
Contravariant (Packer m regs bean) Source # 
Instance details

Defined in Cauldron

Methods

contramap :: (a' -> a) -> Packer m regs bean a -> Packer m regs bean a' #

(>$) :: b -> Packer m regs bean b -> Packer m regs bean a #

value :: forall (m :: Type -> Type) bean. Applicative m => Packer m ('[] :: [Type]) bean bean Source #

For pure constructors that return the bean directly, and do not register secondary beans.

effect :: Applicative m => Packer m ('[] :: [Type]) bean (m bean) Source #

For effectul constructors that return an m bean initialization action, and do not register secondary beans.

Registering secondary beans

Constructors produce a single primary bean, but sometimes they might also "register" a number of secondary beans.

These secondary beans must have Monoid instances and, unlike the primary bean, can be produced by more that one Constructor. Their values are aggregated across all the Constructors that produce them. The final aggregated value can be depended upon by other Constructors as if it were a normal bean.

The Regs type is used to represent the main bean along with the secondary beans that it registers. Because usually we'll be working with functions that do not use the Regs type, a Packer must be used to coax the "tip" of the constructor function into the required shape expected by Constructor.

>>> :{
data A = A deriving Show
data B = B deriving Show
data C = C (Sum Int) deriving Show
makeA :: (Sum Int, A)
makeA = (Sum 1, A)
makeB :: A -> IO (Sum Int, B)
makeB = \_ -> pure (Sum 2, B)
makeC :: Sum Int -> C
makeC = \theSum -> C theSum
:}
>>> :{
do
  let cauldron :: Cauldron IO
      cauldron =
        emptyCauldron
        & insert @A do makeBean do pack (valueWith \(s, a) -> regs1 s a) makeA
        & insert @B do makeBean do pack (effectWith \(s, b) -> regs1 s b) makeB
        & insert @C do makeBean do pack value makeC
      Right (_ :: DependencyGraph, action) = cook forbidDepCycles cauldron
  beans <- action
  pure do taste @C beans
:}
Just (C (Sum {getSum = 3}))

valueWith Source #

Arguments

:: forall (m :: Type -> Type) (regs :: [Type]) r bean. (Applicative m, All (And (Typeable :: Type -> Constraint) Monoid) regs) 
=> (r -> Regs regs bean)

Massage the pure value at the tip of the constructor into a Regs.

-> Packer m regs bean r 
>>> :{
data A = A deriving Show
data B = B deriving Show
makeB :: A -> (Sum Int, B)
makeB = \_ -> (Sum 1, B)
constructorB :: Constructor IO B
constructorB = pack (valueWith \(s,bean) -> regs1 s bean) makeB
:}

effectWith Source #

Arguments

:: forall m (regs :: [Type]) r bean. (Applicative m, All (And (Typeable :: Type -> Constraint) Monoid) regs) 
=> (r -> Regs regs bean)

Massage the value returned by the action at the tip of the constructor into a Regs.

-> Packer m regs bean (m r) 
>>> :{
data A = A deriving Show
data B = B deriving Show
makeB :: A -> IO (Sum Int, B)
makeB = \_ -> pure (Sum 1, B)
constructorB :: Constructor IO B
constructorB = pack (effectWith \(s,bean) -> regs1 s bean) makeB
:}

data Regs (regs :: [Type]) bean Source #

Auxiliary type which contains a primary bean along with zero or more secondary beans. The secondary beans must have Monoid instances.

Instances

Instances details
Functor (Regs regs) Source # 
Instance details

Defined in Cauldron

Methods

fmap :: (a -> b) -> Regs regs a -> Regs regs b #

(<$) :: a -> Regs regs b -> Regs regs a #

regs0 :: bean -> Regs ('[] :: [Type]) bean Source #

A primary bean without secondary beans.

regs1 :: reg1 -> bean -> Regs '[reg1] bean Source #

A primary bean with one secondary bean.

regs2 :: reg1 -> reg2 -> bean -> Regs '[reg1, reg2] bean Source #

A primary bean with two secondary beans.

regs3 :: reg1 -> reg2 -> reg3 -> bean -> Regs '[reg1, reg2, reg3] bean Source #

A primary bean with three secondary beans.

Cooking the beans

cook :: Monad m => Fire m -> Cauldron m -> Either BadBeans (DependencyGraph, m BoiledBeans) Source #

Build the beans using the recipes stored in the Cauldron.

cookNonEmpty :: Monad m => NonEmpty (Fire m, Cauldron m) -> Either BadBeans (NonEmpty DependencyGraph, m (NonEmpty BoiledBeans)) Source #

Cook a 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 BadBeans (Tree DependencyGraph, m (Tree BoiledBeans)) 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.

(Terrible uninformative name caused by a metaphor 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. (BEWARE: Pattern-matching too eagerly on this "bean from the future" during construction will cause infinite loops.)

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

Tasting the results

data BoiledBeans Source #

The successful result of cooking a Cauldron. Can't do a lot with them other than to taste them.

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

Return the resulting bean, if present.

data BadBeans Source #

Sometimes the cooking process goes wrong.

Constructors

MissingDependencies PathToCauldron (Map TypeRep (Set TypeRep))

The Cauldron identified by PathToCauldron has beans that depend on beans that can't be found either in the current Cauldron or its ancestors.

DoubleDutyBeans (Set TypeRep)

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

DependencyCycle (NonEmpty BeanConstructionStep)

Dependency cycles are disallowed by some Fires.

Instances

Instances details
Show BadBeans Source # 
Instance details

Defined in Cauldron

type PathToCauldron = [Int] Source #

Will always be [] when using cook; identifies a Cauldron in a hierarchy of Cauldrons when using cookNonEmpty or cookTree.

Drawing deps

data DependencyGraph Source #

An edge means that the source depends on the target.

The dependencies of each bean are given separatedly from its decorators.

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.

collapsePrimaryBeans :: DependencyGraph -> DependencyGraph Source #

Unifies PrimaryBeans with their respective BarePrimaryBeans and PrimaryBeanDecos.

Also removes any self-loops.

toAdjacencyMap :: DependencyGraph -> AdjacencyMap BeanConstructionStep Source #

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