registry-0.1.1.0: data structure for assembling "components"

Safe HaskellNone
LanguageHaskell2010

Data.Registry.Registry

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.

Registries have a Monoid instance so they can be created incrementally:

 config =
      val (Config 1)
   +: val "hello"
   +: end

 constructors =
   +: fun add1
   +: fun show1
   +: end

 registry =
   config <> constructors

It is also 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
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 #

(<+>) :: Registry is1 os1 -> Registry is2 os2 -> Registry (is1 :++ is2) (os1 :++ os2) 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

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 all the inputs 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

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

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 #

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

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

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

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

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 #

Return singleton 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!

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