Safe Haskell | None |
---|---|
Language | Haskell2010 |
A registry supports the creation of values out of existing values and functions.
It contains 4 parts:
- values: they are available for building anything else and have their exact value can be shown
- functions: they are used to build other values. Only their type can be shown
- specializations: description of specific values to use while trying to build another value of a given type
- modifiers: function to apply to a newly built value before storing it for future use
The <:
operator, to append functions or values to a registry:
registry = val (Config 1) <: val "hello" <: fun add1 <: fun show1
At the type level a list of all the function inputs and all the outputs is being kept to check that when we add a function, all the inputs of that function can be built by the registry. This also ensures that we cannot introduce cycles by adding function which would require each other to build their output
It is possible to use the <+>
operator to "override" some configurations:
mocks = fun noLogging <: fun inMemoryDb mocks <+> registry
Synopsis
- data Registry (inputs :: [Type]) (outputs :: [Type]) = Registry {}
- (<+>) :: Registry is1 os1 -> Registry is2 os2 -> Registry (is1 :++ is2) (os1 :++ os2)
- register :: (Typeable a, IsSubset (Inputs a) out a) => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out)
- registerUnchecked :: Typeable a => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out)
- appendUnchecked :: Typeable a => Registry ins out -> Typed a -> Registry (ins :++ Inputs a) (out :++ '[Output a])
- addTypedUnchecked :: (Typeable a, Typeable b, ins ~ (Inputs a :++ Inputs b), out ~ '[Output a, Output b]) => Typed a -> Typed b -> Registry ins out
- (+:) :: Typeable a => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out)
- class AddRegistryLike a b c | a b -> c where
- (<:) :: a -> b -> c
- class AddRegistryUncheckedLike a b c | a b -> c where
- (<+) :: a -> b -> c
- normalize :: Registry ins out -> Registry (Normalized ins) (Normalized out)
- eraseTypes :: Registry ins out -> Registry '[ERASED_TYPES] '[ERASED_TYPES]
- data ERASED_TYPES
- safeCoerce :: IsSameSet out out1 => Registry ins out -> Registry ins1 out1
- unsafeCoerce :: Registry ins out -> Registry ins1 out1
- end :: Registry '[] '[]
- val :: (Typeable a, Show a) => a -> Typed a
- valTo :: forall m a. (Applicative m, Typeable a, Typeable (m a), Show a) => a -> Typed (m a)
- liftProvidedValue :: forall m a. (Applicative m, Typeable a, Typeable (m a), Show a) => a -> Value
- fun :: Typeable a => a -> Typed a
- funTo :: forall m a b. (ApplyVariadic m a b, Typeable a, Typeable b) => a -> Typed b
- funAs :: forall m a b. (ApplyVariadic1 m a b, Typeable a, Typeable b) => a -> Typed b
- specialize :: forall a b ins out. (Typeable a, Typeable b) => b -> Registry ins out -> Registry ins out
- specializePath :: forall path b ins out. (PathToTypeReps path, Typeable b) => b -> Registry ins out -> Registry ins out
- specializeVal :: forall a b ins out. (Typeable a, Contains a out, Typeable b, Show b) => b -> Registry ins out -> Registry ins out
- specializePathVal :: forall path b ins out. (PathToTypeReps path, Typeable b, Show b) => b -> Registry ins out -> Registry ins out
- specializeValTo :: forall m a b ins out. (Applicative m, Typeable a, Typeable (m b), Typeable b, Show b) => b -> Registry ins out -> Registry ins out
- specializePathValTo :: forall m path b ins out. (Applicative m, PathToTypeReps path, Typeable (m b), Typeable b, Show b) => b -> Registry ins out -> Registry ins out
- class PathToTypeReps (path :: [Type]) where
- someTypeReps :: Proxy path -> NonEmpty SomeTypeRep
- tweak :: forall a ins out. Typeable a => (a -> a) -> Registry ins out -> Registry ins out
- memoize :: forall m a ins out. (MonadIO m, Typeable a, Typeable (m a)) => Registry ins out -> IO (Registry ins out)
- memoizeAll :: forall m ins out. (MonadIO m, MemoizedActions out) => Registry ins out -> IO (Registry ins out)
- newtype MemoizeRegistry (todo :: [Type]) (ins :: [Type]) (out :: [Type]) = MemoizeRegistry {
- _unMemoizeRegistry :: Registry ins out
- startMemoizeRegistry :: Registry ins out -> MemoizeRegistry out ins out
- makeMemoizeRegistry :: forall todo ins out. Registry ins out -> MemoizeRegistry todo ins out
- class MemoizedActions ls where
- memoizeActions :: MemoizeRegistry ls ins out -> IO (MemoizeRegistry '[] ins out)
Documentation
data Registry (inputs :: [Type]) (outputs :: [Type]) Source #
Container for a list of functions or values
Internally all functions and values are stored as Dynamic
values
so that we can access their representation
Instances
(Typeable a, Typeable b, insr ~ (Inputs a :++ Inputs b), outr ~ '[Output a, Output b]) => AddRegistryUncheckedLike (Typed a) (Typed b) (Registry insr outr) Source # | |
(Typeable a, IsSubset (Inputs a) '[Output b] a, Typeable b, insr ~ (Inputs a :++ Inputs b), outr ~ '[Output a, Output b]) => AddRegistryLike (Typed a) (Typed b) (Registry insr outr) Source # | |
(Typeable a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => AddRegistryUncheckedLike (Typed a) (Registry ins2 out2) (Registry insr outr) Source # | |
(Typeable a, IsSubset (Inputs a) out2 a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => AddRegistryLike (Typed a) (Registry ins2 out2) (Registry insr outr) Source # | |
Show (Registry inputs outputs) Source # | |
Semigroup (Registry inputs outputs) Source # | |
Semigroup (Registry inputs outputs) => Monoid (Registry inputs outputs) Source # | |
(Typeable a, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryUncheckedLike (Registry ins2 out2) (Typed a) (Registry insr outr) Source # | |
(Typeable a, IsSubset (Inputs a) out2 a, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryLike (Registry ins2 out2) (Typed a) (Registry insr outr) Source # | |
(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => AddRegistryUncheckedLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # | |
(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => AddRegistryLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # | |
(<+>) :: Registry is1 os1 -> Registry is2 os2 -> Registry (is1 :++ is2) (os1 :++ os2) infixr 4 Source #
Append 2 registries together
register :: (Typeable a, IsSubset (Inputs a) out a) => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out) Source #
Store an element in the registry
Internally elements are stored as Dynamic
values
The signature checks that a constructor of type a
can be fully
constructed from elements of the registry before adding it
registerUnchecked :: Typeable a => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out) Source #
Store an element in the registry
Internally elements are stored as Dynamic
values
appendUnchecked :: Typeable a => Registry ins out -> Typed a -> Registry (ins :++ Inputs a) (out :++ '[Output a]) Source #
Store an element in the registry, at the end of the registry
Internally elements are stored as Dynamic
values
addTypedUnchecked :: (Typeable a, Typeable b, ins ~ (Inputs a :++ Inputs b), out ~ '[Output a, Output b]) => Typed a -> Typed b -> Registry ins out Source #
Add 2 typed values together to form an initial registry
(+:) :: Typeable a => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out) infixr 5 Source #
Add an element to the Registry but do not check that the inputs of a
can already be produced by the registry
class AddRegistryLike a b c | a b -> c where Source #
Instances
(Typeable a, IsSubset (Inputs a) '[Output b] a, Typeable b, insr ~ (Inputs a :++ Inputs b), outr ~ '[Output a, Output b]) => AddRegistryLike (Typed a) (Typed b) (Registry insr outr) Source # | |
(Typeable a, IsSubset (Inputs a) out2 a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => AddRegistryLike (Typed a) (Registry ins2 out2) (Registry insr outr) Source # | |
(Typeable a, IsSubset (Inputs a) out2 a, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryLike (Registry ins2 out2) (Typed a) (Registry insr outr) Source # | |
(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => AddRegistryLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # | |
class AddRegistryUncheckedLike a b c | a b -> c where Source #
Instances
(Typeable a, Typeable b, insr ~ (Inputs a :++ Inputs b), outr ~ '[Output a, Output b]) => AddRegistryUncheckedLike (Typed a) (Typed b) (Registry insr outr) Source # | |
(Typeable a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => AddRegistryUncheckedLike (Typed a) (Registry ins2 out2) (Registry insr outr) Source # | |
(Typeable a, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryUncheckedLike (Registry ins2 out2) (Typed a) (Registry insr outr) Source # | |
(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => AddRegistryUncheckedLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # | |
normalize :: Registry ins out -> Registry (Normalized ins) (Normalized out) Source #
Make the lists of types in the Registry unique, either for better display or for faster compile-time resolution with the make function
eraseTypes :: Registry ins out -> Registry '[ERASED_TYPES] '[ERASED_TYPES] Source #
Remove the parameters list of the registry and replace it with an empty type This makes it easier to read compilation errors where less types are being displayed On the other hand the resulting registry cannot be type-checked anymore when trying to get values out of it
data ERASED_TYPES Source #
safeCoerce :: IsSameSet out out1 => Registry ins out -> Registry ins1 out1 Source #
In case it is hard to show that the types of 2 registries align for example with conditional like if True then fun myFunctionWithKnownOutputs <: r else r
unsafeCoerce :: Registry ins out -> Registry ins1 out1 Source #
And for extreme cases where you know you're doing the right thing but can't prove it
val :: (Typeable a, Show a) => a -> Typed a Source #
Create a value which can be added to the Registry
valTo :: forall m a. (Applicative m, Typeable a, Typeable (m a), Show a) => a -> Typed (m a) Source #
Create a value which can be added to the Registry
and "lift" it to an Applicative
context
liftProvidedValue :: forall m a. (Applicative m, Typeable a, Typeable (m a), Show a) => a -> Value Source #
Create a "lifted" a Value
funTo :: forall m a b. (ApplyVariadic m a b, Typeable a, Typeable b) => a -> Typed b Source #
This is a shortcut to fun . allTo
where allTo
lifts all the inputs and output
to an Applicative
context
funAs :: forall m a b. (ApplyVariadic1 m a b, Typeable a, Typeable b) => a -> Typed b Source #
This is a shortcut to fun . argsTo
where allTo
lifts the inputs only
to an Applicative
context
In general funTo
should work, even with function already returning an m a
but if this is not the case (see issue #7) then funAs can be used
specialize :: forall a b ins out. (Typeable a, Typeable b) => b -> Registry ins out -> Registry ins out Source #
For a given type a
being currently built
when a value of type b
is required pass a specific
value
specializePath :: forall path b ins out. (PathToTypeReps path, Typeable b) => b -> Registry ins out -> Registry ins out Source #
specializeVal :: forall a b ins out. (Typeable a, Contains a out, Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #
specializePathVal :: forall path b ins out. (PathToTypeReps path, Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #
specializeValTo :: forall m a b ins out. (Applicative m, Typeable a, Typeable (m b), Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #
specializePathValTo :: forall m path b ins out. (Applicative m, PathToTypeReps path, Typeable (m b), Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #
class PathToTypeReps (path :: [Type]) where Source #
Typeclass for extracting type representations out of a list of types
someTypeReps :: Proxy path -> NonEmpty SomeTypeRep Source #
Instances
(Typeable a, PathToTypeReps rest) => PathToTypeReps (a ': rest) Source # | |
Defined in Data.Registry.Registry someTypeReps :: Proxy (a ': rest) -> NonEmpty SomeTypeRep Source # | |
Typeable a => PathToTypeReps '[a] Source # | |
Defined in Data.Registry.Registry someTypeReps :: Proxy '[a] -> NonEmpty SomeTypeRep Source # |
tweak :: forall a ins out. Typeable a => (a -> a) -> Registry ins out -> Registry ins out Source #
Once a value has been computed allow to modify it before storing it This keeps the same registry type
Memoization
memoize :: forall m a ins out. (MonadIO m, Typeable a, Typeable (m a)) => Registry ins out -> IO (Registry ins out) Source #
Instantiating components can trigger side-effects The way the resolution algorithm works a component of type `m a` will be re-executed *everytime* it is needed as a given dependency This section adds support for memoizing those actions
Return memoized values for a monadic type
Note that the returned Registry is in IO
because we are caching a value
and this is a side-effect!
memoizeAll :: forall m ins out. (MonadIO m, MemoizedActions out) => Registry ins out -> IO (Registry ins out) Source #
Memoize *all* the output actions of a Registry when they are creating effectful components
This relies on a helper data structure MemoizeRegistry
tracking the types already
memoized and a typeclass MemoizedActions going through the list of out
types to process them
one by one. Note that a type of the form a
will not be memoized (only `m a`)
newtype MemoizeRegistry (todo :: [Type]) (ins :: [Type]) (out :: [Type]) Source #
MemoizeRegistry | |
|
startMemoizeRegistry :: Registry ins out -> MemoizeRegistry out ins out Source #
makeMemoizeRegistry :: forall todo ins out. Registry ins out -> MemoizeRegistry todo ins out Source #
class MemoizedActions ls where Source #
memoizeActions :: MemoizeRegistry ls ins out -> IO (MemoizeRegistry '[] ins out) Source #
Instances
MemoizedActions ('[] :: [Type]) Source # | |
Defined in Data.Registry.Registry memoizeActions :: forall (ins :: [Type]) (out :: [Type]). MemoizeRegistry '[] ins out -> IO (MemoizeRegistry '[] ins out) Source # | |
MemoizedActions rest => MemoizedActions (a ': rest) Source # | |
Defined in Data.Registry.Registry memoizeActions :: forall (ins :: [Type]) (out :: [Type]). MemoizeRegistry (a ': rest) ins out -> IO (MemoizeRegistry '[] ins out) Source # | |
(MonadIO m, Typeable a, Typeable (m a), MemoizedActions rest) => MemoizedActions (m a ': rest) Source # | |
Defined in Data.Registry.Registry memoizeActions :: forall (ins :: [Type]) (out :: [Type]). MemoizeRegistry (m a ': rest) ins out -> IO (MemoizeRegistry '[] ins out) Source # |