registry-0.1.7.0: data structure for assembling components

Safe HaskellNone
LanguageHaskell2010

Data.Registry.Registry

Contents

Description

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

A registry is created by using the +: operator, adding functions or values to the empty end registry:

registry =
     val (Config 1)
  +: val "hello"
  +: fun add1
  +: fun show1
  +: end

At the type level a list of all the function inputs and all the outputs is being kept to allow some checks to be made when we want to build a value out of the registry.

It is possible to use the <+> operator to "override" some configurations:

 mocks =
      fun noLogging
   +: fun inMemoryDb
   +: end

 mocks <+> registry
Synopsis

Documentation

data Registry (inputs :: [*]) (outputs :: [*]) 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 :++ ([] :: [Type]))), outr ~ (Output a ': (Output b ': ([] :: [Type])))) => 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, 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 #

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 #

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 #

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 #

(Typeable a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => 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 #

(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => 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 #

(<+>) :: Registry is1 os1 -> Registry is2 os2 -> Registry (is1 :++ is2) (os1 :++ os2) infixr 4 Source #

Append 2 registries together

register :: 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

(+:) :: Typeable a => Typed a -> Registry ins out -> Registry (Inputs a :++ ins) (Output a ': out) infixr 5 Source #

Add an element to the Registry - Alternative to register where the parentheses can be ommitted

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

Methods

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

Instances
(Typeable a, Typeable b, insr ~ (Inputs a :++ (Inputs b :++ ([] :: [Type]))), outr ~ (Output a ': (Output b ': ([] :: [Type])))) => 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, 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 #

(Typeable a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => 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 #

(insr ~ (ins1 :++ ins2), outr ~ (out1 :++ out2)) => 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 #

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

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

specialize :: forall a b ins out. (Typeable a, Contains a out, 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, IsSubset path out, 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 #

This is similar to specialize but additionally uses the Show instance of b to display more information when printing the registry out

specializePathVal :: forall path b ins out. (PathToTypeReps path, IsSubset path out, Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #

specializeValTo :: forall m a b ins out. (Applicative m, Typeable a, Contains a out, 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, IsSubset path out, Typeable (m b), Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #

specializeUnsafe :: 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

specializePathUnsafe :: forall path b ins out. (PathToTypeReps path, Typeable b) => b -> Registry ins out -> Registry ins out Source #

specializeUnsafeVal :: forall a b ins out. (Typeable a, Contains a out, Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #

specializePathUnsafeVal :: forall path b ins out. (PathToTypeReps path, Typeable b, Show b) => b -> Registry ins out -> Registry ins out Source #

specializeUnsafeValTo :: 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 #

specializePathUnsafeValTo :: 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 :: [*]) where Source #

Typeclass for extracting type representations out of a list of types

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

Defined in Data.Registry.Registry

Methods

someTypeReps :: Proxy (a ': rest) -> NonEmpty SomeTypeRep Source #

Typeable a => PathToTypeReps (a ': ([] :: [Type])) Source # 
Instance details

Defined in Data.Registry.Registry

tweak :: forall a ins out. (Typeable a, Contains a out) => (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

tweakUnsafe :: 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

Memoization

memoize :: forall m a ins out. (MonadIO m, Typeable a, Typeable (m a), Contains (m a) out) => 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 (component creation + optional warmup)

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!

memoizeUnsafe :: forall m a ins out. (MonadIO m, Typeable a, Typeable (m a)) => Registry ins out -> IO (Registry ins out) Source #

Memoize an action for a given type but don't check if the value is part of the registry outputs

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 :: [*]) (ins :: [*]) (out :: [*]) Source #

Constructors

MemoizeRegistry 

Fields

makeMemoizeRegistry :: forall todo ins out. Registry ins out -> MemoizeRegistry todo ins out Source #

class MemoizedActions ls where Source #

Methods

memoizeActions :: MemoizeRegistry ls ins out -> IO (MemoizeRegistry '[] ins out) Source #

Instances
MemoizedActions ([] :: [Type]) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

memoizeActions :: MemoizeRegistry [] ins out -> IO (MemoizeRegistry [] ins out) Source #

MemoizedActions rest => MemoizedActions (a ': rest) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

memoizeActions :: MemoizeRegistry (a ': rest) ins out -> IO (MemoizeRegistry [] ins out) Source #

(MonadIO m, Typeable a, Typeable (m a), MemoizedActions rest) => MemoizedActions (m a ': rest) Source # 
Instance details

Defined in Data.Registry.Registry

Methods

memoizeActions :: MemoizeRegistry (m a ': rest) ins out -> IO (MemoizeRegistry [] ins out) Source #

DEPRECATIONS

singleton :: forall m a ins out. (MonadIO m, Typeable a, Typeable (m a), Contains (m a) out) => Registry ins out -> IO (Registry ins out) Source #

Deprecated: use memoize instead

singletonUnsafe :: forall m a ins out. (MonadIO m, Typeable a, Typeable (m a)) => Registry ins out -> IO (Registry ins out) Source #

Deprecated: use memoizeUnsafe instead