registry-0.1.2.6: data structure for assembling components

Safe HaskellNone
LanguageHaskell2010

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 If a Context is present for a a created value this means that this value has been written as the result of a specialization. The first type of the list of types in the context is the types under which the specialization must apply and the other types are "parents" of the current value in the value graph

Instances
Show Value Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Hashable Value Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

data ValueDescription Source #

This registers the specific context in which a valu | 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

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

specializationContext :: Value -> Maybe Context Source #

Return the creation context for a given value when it was created as the result of a "specialization"

usedSpecialization :: Value -> Maybe Specialization Source #

Return the specialization used to create a specific values

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
Show Function Source # 
Instance details

Defined in Data.Registry.Internal.Types

createFunction :: Typeable a => a -> 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

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

newtype Functions Source #

This is a list of functions (or "constructors") available for constructing values

Constructors

Functions [Function] 

describeFunctions :: Functions -> Text Source #

Display a list of constructors

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

Add one more Function to the list of Functions

newtype Values Source #

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

Constructors

Values 

Fields

Instances
Show Values Source # 
Instance details

Defined in Data.Registry.Internal.Types

Semigroup Values Source # 
Instance details

Defined in Data.Registry.Internal.Types

Monoid Values Source # 
Instance details

Defined in Data.Registry.Internal.Types

describeValues :: Values -> Text Source #

Display a list of values

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

Add one more Value to the list of Values

newtype Context Source #

The types of values that we are trying to build at a given moment of the resolution algorithm. IMPORTANT: this is a *stack*, the deepest elements in the value graph are first in the list

Constructors

Context 
Instances
Eq Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

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

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

Show Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Semigroup Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Monoid Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Hashable Context Source # 
Instance details

Defined in Data.Registry.Internal.Types

Methods

hashWithSalt :: Int -> Context -> Int #

hash :: Context -> Int #

dependenciesOn :: Value -> Dependencies Source #

The dependencies of a value + the value itself

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

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

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 specifications valid in a given context

specializedContext :: Context -> Specialization -> SpecializedContext 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 SpecializedContext 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
Eq SpecializedContext Source # 
Instance details

Defined in Data.Registry.Internal.Types

Ord SpecializedContext Source #

A specialization range is preferrable 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

Show SpecializedContext Source # 
Instance details

Defined in Data.Registry.Internal.Types

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

Restrict a given context to the types of a specialization specializedContext :: Context -> Specialization -> Context specializedContext (Context cs) specialization = Context $ P.dropWhile (/= specializationEnd specialization) . dropWhileEnd (/= specializationStart specialization) $ cs

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

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

Constructors

Modifiers [(SomeTypeRep, Function)] 

describeModifiers :: Modifiers -> Text Source #

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