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

Data.Registry.Internal.Types

Description

List of types used inside the Registry

Synopsis

Documentation

data Value Source #

A Value is the Dynamic representation of a Haskell value + its description It is either provided by the user of the Registry or created as part of the resolution algorithm.

A value can simply be provided by the user of the registry or created as the result of function application

Dependencies is the transitive list of all the values used to create a CreatedValue

The optional SpecializationContext is used for values created as the result of a specialization It stores the context of creation (the list of types we are currently trying to build) and the desired specialization (which must be a subtype of the context)

Instances

Instances details
Show Value Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Hashable Value Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

hashWithSalt :: Int -> Value -> Int

hash :: Value -> Int

data ValueDescription Source #

Description of a value. It might just have a description for its type when it is a value created by the resolution algorithm

describeValue :: (Typeable a, Show a) => a -> ValueDescription Source #

Describe a value with its type and actual content

describeTypeableValue :: Typeable a => a -> ValueDescription Source #

Describe a value with only its type

showValue :: Value -> Text Source #

Show a Value from the Registry

createValue :: (Typeable a, Show a) => a -> Value Source #

Create a Value from a Haskell value, using its Show instance for its description

makeCreatedValue :: Dynamic -> ValueDescription -> Dependencies -> Value Source #

make a CreatedValue in no particular context

createTypeableValue :: Typeable a => a -> Value Source #

Create a Value from a Haskell value, with only its Typeable description

createDynValue :: Dynamic -> Text -> Value Source #

Create a Value from a Dynamic value and some description

valueDynTypeRep :: Value -> SomeTypeRep Source #

Type representation of a Value

valueDyn :: Value -> Dynamic Source #

Dynamic representation of a Value

valDescription :: Value -> ValueDescription Source #

The description for a Value

valueDependencies :: Value -> Dependencies Source #

The dependencies for a Value

valDescriptionToText :: ValueDescription -> Text Source #

A ValueDescription as Text. If the actual content of the Value is provided display the type first then the content

valueSpecialization :: Value -> Maybe Specialization Source #

Return the specialization used when specializing a value

isInSpecializationContext :: SomeTypeRep -> Value -> Bool Source #

Return True if a type is part of the specialization context of a Value

hasSpecializedDependencies :: Specializations -> Value -> Bool Source #

Return True if a value has transitives dependencies which are specialized values

data Function Source #

A Function is the Dynamic representation of a Haskell function + its description

Instances

Instances details
Show Function Source # 
Instance details

Defined in Data.Registry.Internal.Types

createFunction :: Typeable f => f -> Function Source #

Create a Function value from a Haskell function

describeFunction :: Typeable a => a -> FunctionDescription Source #

Describe a Function (which doesn't have a Show instance) that can be put in the Registry

showFunction :: Function -> Text Source #

Show a Function as Text using its Description

funDyn :: Function -> Dynamic Source #

Dynamic representation of a Function

funDynTypeRep :: Function -> SomeTypeRep Source #

Type representation of a Function

funDynOutTypeRep :: Function -> SomeTypeRep Source #

Type representation of the output of a Function

hasParameters :: Function -> Bool Source #

Return True if a Function has some input parameters

data Typed a Source #

A Typed value or function can be added to a Registry It is either a value, having both Show and Typeable information or a function having just Typeable information

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 #

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

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

data Untyped Source #

A Untyped is used for storing either a value or a function in a specialization

Instances

Instances details
Show Untyped Source # 
Instance details

Defined in Data.Registry.Internal.Types

untype :: Typed a -> Untyped Source #

Drop the type variable

newtype Functions Source #

This is a list of functions (or "constructors") available for constructing values They are sorted by output type and if there are several available functions for a given type the first function in the list has the highest priority

Constructors

Functions 

Fields

fromFunctions :: [Function] -> Functions Source #

Create a Functions data structure from a list of functions

toFunctions :: Functions -> [Function] Source #

Create a list of functions from the Functions data structure

describeFunctions :: Functions -> Text Source #

Display a list of constructors

addFunction :: Function -> Functions -> Functions Source #

Add one more Function to the list of Functions. It gets the highest priority for functions with the same output type

appendFunction :: Function -> Functions -> Functions Source #

Add one more Function to the list of Functions It gets the lowest priority for functions with the same output type This is not a very efficient because it requires a full recreation of the map

findFunction :: SomeTypeRep -> Functions -> Maybe Function Source #

Find a constructor function returning a target type from a list of constructors

newtype Values Source #

List of values available which can be used as parameters to constructors for building other values

Constructors

Values 

Fields

Instances

Instances details
Monoid Values Source # 
Instance details

Defined in Data.Registry.Internal.Types

Semigroup Values Source # 
Instance details

Defined in Data.Registry.Internal.Types

Show Values Source # 
Instance details

Defined in Data.Registry.Internal.Types

fromValues :: [Value] -> Values Source #

Create a Values data structure from a list of values

toValues :: Values -> [Value] Source #

Create a list of values from the Values data structure

describeValues :: Values -> Text Source #

Display a list of values

addValue :: Value -> Values -> Values Source #

Add one more Value to the list of Values

appendValue :: Value -> Values -> Values Source #

Add one more Value to the list of Values It gets the lowest priority for values with the same type This is not a very efficient because it requires a full recreation of the map

findValues :: SomeTypeRep -> Values -> [Value] Source #

Find all the values with a specific type from a list of constructors

newtype Context Source #

The types of values that we are trying to build at a given moment of the resolution algorithm. We also store the function requiring a given value type to provide better error messages IMPORTANT: this is a *stack*, the deepest elements in the value graph are first in the list

Constructors

Context 

Instances

Instances details
Monoid Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Semigroup Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Show Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Eq Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

(==) :: Context -> Context -> Bool #

(/=) :: Context -> Context -> Bool #

contextTypes :: Context -> [SomeTypeRep] Source #

Return the target types for a given context

dependenciesTypes :: Dependencies -> DependenciesTypes Source #

Return the types of all the dependencies

dependenciesOn :: Value -> Dependencies Source #

The dependencies of a value + the value itself

newtype Specializations Source #

Specification of values which become available for construction when a corresponding type comes in context

data Specialization Source #

A specialization is defined by a path of types, from top to bottom in the value graph and target value, which is the value to use when we need a value on that type on that path. For example: specializationPath = [App, PaymentEngine, TransactionRepository] specializationValue = DatabaseConfig "localhost" 5432 This means that need to use this DatabaseConfig whenever trying to find inputs needed to create a TransactionRepository if that repository is necessary to create a PaymentEngine, itself involved in the creation of the App

Instances

Instances details
Show Specialization Source # 
Instance details

Defined in Data.Registry.Internal.Types

type SpecializationPath = NonEmpty SomeTypeRep Source #

List of consecutive types used when making a specific values See the comments on Specialization

specializationPaths :: Value -> Maybe [SpecializationPath] Source #

Return the various specialization paths which have possibly led to the creation of that value

specializationStart :: Specialization -> SomeTypeRep Source #

First type of a specialization

specializationEnd :: Specialization -> SomeTypeRep Source #

Last type of a specialization

specializationTargetType :: Specialization -> SomeTypeRep Source #

Return the type of the replaced value in a specialization

data SpecializationContext Source #

This represents the full context in which a value has been specialized Context is the full list of types leading to the creation of that value and Specialization is a sub path describing under which types the value must be specialized For example, when creating a FilePath used by a Logger the context could be: App -> Database -> Sql -> Logger and the Specialization just Database -> Logger to specify that the file path must have a specific value in that case

isContextApplicable :: Context -> Specialization -> Bool Source #

A specialization is applicable to a context if all its types are part of that context, in the right order

applicableTo :: Specializations -> Context -> Specializations Source #

Return the specializations valid in a given context Those are the specializations which path is a subpath of the current context

specializationRange :: Context -> Specialization -> SpecializationRange Source #

The depth of a specialization in a context is the the index of the "deepest" type of that specialization in the stack of types of that context is the one having its "deepest" type (in the value graph) the "deepest" in the current context If there is a tie we take the "highest" highest type of each

data SpecializationRange Source #

For a given context this represents the position of a specialization path in that context. startRange is the index of the start type of the specialization endRange is the index of the last type.

Instances

Instances details
Show SpecializationRange Source # 
Instance details

Defined in Data.Registry.Internal.Types

Eq SpecializationRange Source # 
Instance details

Defined in Data.Registry.Internal.Types

Ord SpecializationRange Source #

A specialization range is preferable to another one if its types are more specific (or "deepest" in the value graph) than the other If a path is limited to just one type then a path ending with the same type but specifying other types will take precedence See TypesSpec for some concrete examples.

Instance details

Defined in Data.Registry.Internal.Types

createValueFromSpecialization :: Context -> Specialization -> Untyped Source #

In a given context, create a value as specified by a specialization the full context is necessary since the specificationPath is only a subpath of a given creation context Note: there are no dependencies for this value since it has been directly provided by a Specialization

describeSpecializations :: Specializations -> Text Source #

Display a list of specializations for the Registry, just showing the context (a type) in which a value must be selected

newtype Modifiers Source #

List of functions modifying some values right after they have been built. This enables "tweaking" the creation process with slightly different results. Here SomeTypeRep is the target value type a and

type ModifierFunction = Maybe [SpecializationPath] -> Function Source #

A ModifierFunction modifies an already created value If that value has been created as the result of a specialization then the specialization path is also passed to the function This is used for memoizing actions using a cache so that we cache each specialized value separately.

createConstModifierFunction :: Typeable f => f -> ModifierFunction Source #

Create a ModifierFunction value from a Haskell function The application of that function does not depend on the fact that we are trying to apply it to a specialized value

describeModifiers :: Modifiers -> Text Source #

Display a list of modifiers for the Registry, just showing the type of the modified value