registry-0.6.0.0: data structure for assembling components
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Registry.Registry

Description

A registry supports the creation of values out of existing values and functions.

It contains 3 parts:

  • entries: they can be either values or functions used to create values
  • 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

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

Instances details
Semigroup (Registry inputs outputs) => Monoid (Registry inputs outputs) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

mempty :: Registry inputs outputs #

mappend :: Registry inputs outputs -> Registry inputs outputs -> Registry inputs outputs #

mconcat :: [Registry inputs outputs] -> Registry inputs outputs #

Semigroup (Registry inputs outputs) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<>) :: Registry inputs outputs -> Registry inputs outputs -> Registry inputs outputs #

sconcat :: NonEmpty (Registry inputs outputs) -> Registry inputs outputs #

stimes :: Integral b => b -> Registry inputs outputs -> Registry inputs outputs #

Show (Registry inputs outputs) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

showsPrec :: Int -> Registry inputs outputs -> ShowS #

show :: Registry inputs outputs -> String #

showList :: [Registry inputs outputs] -> ShowS #

(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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: 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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: Typed a -> Registry ins2 out2 -> Registry insr outr Source #

(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2), AreSubset ins1 outr out1) => AddRegistryLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: Registry ins1 out1 -> Registry ins2 out2 -> Registry insr outr Source #

(Typeable a, AreSubset ins2 outr out2, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryLike (Registry ins2 out2) (Typed a) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: Registry ins2 out2 -> Typed a -> Registry insr outr Source #

(Typeable a, Typeable b, insr ~ (Inputs a :++ Inputs b), outr ~ '[Output a, Output b]) => AddRegistryUncheckedLike (Typed a) (Typed b) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: 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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: Typed a -> Registry ins2 out2 -> Registry insr outr Source #

(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => AddRegistryUncheckedLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: Registry ins1 out1 -> 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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: Registry ins2 out2 -> Typed a -> 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

Prepend an element to the registry with no checks at all

class AddRegistryLike a b c | a b -> c where Source #

Typeclass for appending values and or registries together, with static checks

Methods

(<:) :: a -> b -> c infixr 5 Source #

Instances

Instances details
(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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: 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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: Typed a -> Registry ins2 out2 -> Registry insr outr Source #

(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2), AreSubset ins1 outr out1) => AddRegistryLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: Registry ins1 out1 -> Registry ins2 out2 -> Registry insr outr Source #

(Typeable a, AreSubset ins2 outr out2, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryLike (Registry ins2 out2) (Typed a) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<:) :: Registry ins2 out2 -> Typed a -> Registry insr outr Source #

class AddRegistryUncheckedLike a b c | a b -> c where Source #

Typeclass for appending values and or registries together, without static checks

Methods

(<+) :: a -> b -> c infixr 5 Source #

Instances

Instances details
(Typeable a, Typeable b, insr ~ (Inputs a :++ Inputs b), outr ~ '[Output a, Output b]) => AddRegistryUncheckedLike (Typed a) (Typed b) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: 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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: Typed a -> Registry ins2 out2 -> Registry insr outr Source #

(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => AddRegistryUncheckedLike (Registry ins1 out1) (Registry ins2 out2) (Registry insr outr) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: Registry ins1 out1 -> 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 # 
Instance details

Defined in Data.Registry.Registry

Methods

(<+) :: Registry ins2 out2 -> Typed a -> 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 #

Singleton type representing erased types

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

end :: Registry '[] '[] Source #

The empty Registry

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

fun :: Typeable a => a -> Typed a Source #

Create a function which can be added to the Registry

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 => Typed 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 => Typed b -> Registry ins out -> Registry ins out Source #

Specialize a function for a specific path of types

class PathToTypeReps (path :: [Type]) where Source #

Typeclass for extracting type representations out of a list of types

Instances

Instances details
Typeable a => PathToTypeReps '[a] Source # 
Instance details

Defined in Data.Registry.Registry

(Typeable a, PathToTypeReps rest) => PathToTypeReps (a ': rest) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

someTypeReps :: Proxy (a ': rest) -> 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

tweakUnspecialized :: 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 This only tweaks unspecialized values!