Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
List of types used inside the Registry
Synopsis
- data Value
- data ValueDescription = ValueDescription {
- _valueType :: Text
- _valueValue :: Maybe Text
- describeValue :: (Typeable a, Show a) => a -> ValueDescription
- describeTypeableValue :: Typeable a => a -> ValueDescription
- showValue :: Value -> Text
- createValue :: (Typeable a, Show a) => a -> Value
- makeProvidedValue :: Dynamic -> ValueDescription -> Value
- makeCreatedValue :: Dynamic -> ValueDescription -> Dependencies -> Value
- createTypeableValue :: Typeable a => a -> Value
- createDynValue :: Dynamic -> Text -> Value
- valueDynTypeRep :: Value -> SomeTypeRep
- valueDyn :: Value -> Dynamic
- valDescription :: Value -> ValueDescription
- valueDependencies :: Value -> Dependencies
- valDescriptionToText :: ValueDescription -> Text
- valueSpecializationContext :: Value -> Maybe SpecializationContext
- valueContext :: Value -> Maybe Context
- valueSpecialization :: Value -> Maybe Specialization
- isInSpecializationContext :: SomeTypeRep -> Value -> Bool
- hasSpecializedDependencies :: Specializations -> Value -> Bool
- data Function = Function Dynamic FunctionDescription
- createFunction :: Typeable f => f -> Function
- data FunctionDescription = FunctionDescription {
- _inputTypes :: [Text]
- _outputType :: Text
- describeFunction :: Typeable a => a -> FunctionDescription
- showFunction :: Function -> Text
- funDescription :: Function -> FunctionDescription
- funDyn :: Function -> Dynamic
- funDynTypeRep :: Function -> SomeTypeRep
- funDescriptionToText :: FunctionDescription -> Text
- hasParameters :: Function -> Bool
- data Typed a
- newtype Functions = Functions [Function]
- describeFunctions :: Functions -> Text
- addFunction :: Function -> Functions -> Functions
- newtype Values = Values {}
- describeValues :: Values -> Text
- addValue :: Value -> Values -> Values
- newtype Context = Context {
- _contextStack :: [(SomeTypeRep, Maybe SomeTypeRep)]
- contextTypes :: Context -> [SomeTypeRep]
- newtype Dependencies = Dependencies {
- unDependencies :: [Value]
- newtype DependenciesTypes = DependenciesTypes {}
- dependenciesTypes :: Dependencies -> DependenciesTypes
- dependenciesOn :: Value -> Dependencies
- newtype Specializations = Specializations {}
- data Specialization = Specialization {}
- type SpecializationPath = NonEmpty SomeTypeRep
- specializationPaths :: Value -> Maybe [SpecializationPath]
- specializationStart :: Specialization -> SomeTypeRep
- specializationEnd :: Specialization -> SomeTypeRep
- specializationTargetType :: Specialization -> SomeTypeRep
- data SpecializationContext = SpecializationContext {}
- isContextApplicable :: Context -> Specialization -> Bool
- applicableTo :: Specializations -> Context -> Specializations
- specializationRange :: Context -> Specialization -> SpecializationRange
- data SpecializationRange = SpecializationRange {}
- createValueFromSpecialization :: Context -> Specialization -> Value
- describeSpecializations :: Specializations -> Text
- newtype Modifiers = Modifiers [(SomeTypeRep, ModifierFunction)]
- type ModifierFunction = Maybe [SpecializationPath] -> Function
- createConstModifierFunction :: Typeable f => f -> ModifierFunction
- describeModifiers :: Modifiers -> Text
Documentation
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)
CreatedValue Dynamic ValueDescription (Maybe SpecializationContext) Dependencies | |
ProvidedValue Dynamic ValueDescription |
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
Instances
Show ValueDescription Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> ValueDescription -> ShowS # show :: ValueDescription -> String # showList :: [ValueDescription] -> ShowS # | |
Eq ValueDescription Source # | |
Defined in Data.Registry.Internal.Types (==) :: ValueDescription -> ValueDescription -> Bool # (/=) :: ValueDescription -> ValueDescription -> Bool # | |
Hashable ValueDescription Source # | |
Defined in Data.Registry.Internal.Types hashWithSalt :: Int -> ValueDescription -> Int hash :: ValueDescription -> Int |
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
createValue :: (Typeable a, Show a) => a -> Value Source #
Create a Value from a Haskell value, using its Show instance for its description
makeProvidedValue :: Dynamic -> ValueDescription -> Value Source #
Make a ProvidedValue
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
valDescription :: Value -> ValueDescription Source #
The description for a Value
valueDependencies :: Value -> Dependencies Source #
The dependencies for a Value
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
A Function is the Dynamic
representation of a Haskell function + its description
createFunction :: Typeable f => f -> Function Source #
Create a Function
value from a Haskell function
data FunctionDescription Source #
Description of a Function
with input types and output type
Instances
Show FunctionDescription Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> FunctionDescription -> ShowS # show :: FunctionDescription -> String # showList :: [FunctionDescription] -> ShowS # | |
Eq FunctionDescription Source # | |
Defined in Data.Registry.Internal.Types (==) :: FunctionDescription -> FunctionDescription -> Bool # (/=) :: FunctionDescription -> FunctionDescription -> Bool # |
describeFunction :: Typeable a => a -> FunctionDescription Source #
funDescription :: Function -> FunctionDescription Source #
The Description of a Function
funDynTypeRep :: Function -> SomeTypeRep Source #
Type representation of a Function
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
(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 # | |
(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 # | |
(Typeable a, IsSubset (Inputs a) out2 a, insr ~ (ins2 :++ Inputs a), outr ~ (out2 :++ '[Output a])) => AddRegistryLike (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 # | |
(Typeable a, insr ~ (Inputs a :++ ins2), outr ~ (Output a ': out2)) => AddRegistryUncheckedLike (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 # | |
This is a list of functions (or "constructors") available for constructing values
describeFunctions :: Functions -> Text Source #
Display a list of constructors
addFunction :: Function -> Functions -> Functions Source #
Add one more Function to the list of Functions
List of values available which can be used as parameters to constructors for building other values
describeValues :: Values -> Text Source #
Display a list of values
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
Context | |
|
contextTypes :: Context -> [SomeTypeRep] Source #
Return the target types for a given context
newtype Dependencies Source #
The values that a value depends on
Instances
Monoid Dependencies Source # | |
Defined in Data.Registry.Internal.Types mempty :: Dependencies # mappend :: Dependencies -> Dependencies -> Dependencies # mconcat :: [Dependencies] -> Dependencies # | |
Semigroup Dependencies Source # | |
Defined in Data.Registry.Internal.Types (<>) :: Dependencies -> Dependencies -> Dependencies # sconcat :: NonEmpty Dependencies -> Dependencies # stimes :: Integral b => b -> Dependencies -> Dependencies # | |
Show Dependencies Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> Dependencies -> ShowS # show :: Dependencies -> String # showList :: [Dependencies] -> ShowS # | |
Eq Dependencies Source # | |
Defined in Data.Registry.Internal.Types (==) :: Dependencies -> Dependencies -> Bool # (/=) :: Dependencies -> Dependencies -> Bool # |
newtype DependenciesTypes Source #
The values types that a value depends on
Instances
Monoid DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types | |
Semigroup DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types (<>) :: DependenciesTypes -> DependenciesTypes -> DependenciesTypes # sconcat :: NonEmpty DependenciesTypes -> DependenciesTypes # stimes :: Integral b => b -> DependenciesTypes -> DependenciesTypes # | |
Show DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> DependenciesTypes -> ShowS # show :: DependenciesTypes -> String # showList :: [DependenciesTypes] -> ShowS # | |
Eq DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types (==) :: DependenciesTypes -> DependenciesTypes -> Bool # (/=) :: DependenciesTypes -> DependenciesTypes -> Bool # |
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
Instances
Monoid Specializations Source # | |
Defined in Data.Registry.Internal.Types mappend :: Specializations -> Specializations -> Specializations # mconcat :: [Specializations] -> Specializations # | |
Semigroup Specializations Source # | |
Defined in Data.Registry.Internal.Types (<>) :: Specializations -> Specializations -> Specializations # sconcat :: NonEmpty Specializations -> Specializations # stimes :: Integral b => b -> Specializations -> Specializations # | |
Show Specializations Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> Specializations -> ShowS # show :: Specializations -> String # showList :: [Specializations] -> ShowS # |
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
Show Specialization Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> Specialization -> ShowS # show :: Specialization -> String # showList :: [Specialization] -> ShowS # | |
Eq Specialization Source # | |
Defined in Data.Registry.Internal.Types (==) :: Specialization -> Specialization -> Bool # (/=) :: Specialization -> Specialization -> Bool # |
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
Instances
Show SpecializationContext Source # | |
Defined in Data.Registry.Internal.Types showsPrec :: Int -> SpecializationContext -> ShowS # show :: SpecializationContext -> String # showList :: [SpecializationContext] -> ShowS # | |
Eq SpecializationContext Source # | |
Defined in Data.Registry.Internal.Types (==) :: SpecializationContext -> SpecializationContext -> Bool # (/=) :: SpecializationContext -> SpecializationContext -> Bool # |
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
createValueFromSpecialization :: Context -> Specialization -> Value 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
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