Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Data.Registry.Internal.Types
Contents
Description
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
- funDynOutTypeRep :: Function -> SomeTypeRep
- funDescriptionToText :: FunctionDescription -> Text
- hasParameters :: Function -> Bool
- data Typed a
- data Untyped
- untype :: Typed a -> Untyped
- outTypeRep :: Untyped -> SomeTypeRep
- untypedDyn :: Untyped -> Dynamic
- newtype Entries = Entries {}
- fromUntyped :: [Untyped] -> Entries
- toFunctions :: Entries -> [Function]
- toValues :: Entries -> [Value]
- describeFunctions :: Entries -> Text
- describeValues :: Entries -> Text
- addUntyped :: Untyped -> Entries -> Entries
- addEntry :: Typed a -> Entries -> Entries
- appendUntyped :: Untyped -> Entries -> Entries
- appendEntry :: Typed a -> Entries -> Entries
- findUntyped :: SomeTypeRep -> Entries -> Maybe Untyped
- newtype Context = Context {
- _contextStack :: [(SomeTypeRep, Maybe SomeTypeRep)]
- contextTypes :: Context -> [SomeTypeRep]
- newtype Dependencies = Dependencies {
- unDependencies :: [Value]
- newtype DependenciesTypes = DependenciesTypes {}
- dependenciesTypes :: Dependencies -> DependenciesTypes
- dependenciesOf :: Value -> Dependencies
- newtype Specializations = Specializations {}
- data Specialization = Specialization {}
- type SpecializationPath = NonEmpty SomeTypeRep
- specializedContexts :: Value -> [SpecializationContext]
- 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 -> Untyped
- describeSpecializations :: Specializations -> Text
- newtype Modifiers = Modifiers [(SomeTypeRep, ModifierFunction)]
- type ModifierFunction = [SpecializationContext] -> Function
- createConstModifierFunction :: Typeable f => f -> ModifierFunction
- createUnspecializedModifierFunction :: forall a f. (Typeable f, Typeable a, Typeable (a -> a)) => f -> ModifierFunction
- describeModifiers :: Modifiers -> Text
- newtype Values = Values {}
- fromValues :: [Value] -> Values
- listValues :: Values -> [Value]
- addValue :: Value -> Values -> Values
- appendValue :: Value -> Values -> Values
- findValues :: SomeTypeRep -> Values -> [Value]
- findValue :: SomeTypeRep -> Values -> Maybe Value
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)
Constructors
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
Constructors
ValueDescription | |
Fields
|
Instances
Show ValueDescription Source # | |
Defined in Data.Registry.Internal.Types Methods showsPrec :: Int -> ValueDescription -> ShowS # show :: ValueDescription -> String # showList :: [ValueDescription] -> ShowS # | |
Eq ValueDescription Source # | |
Defined in Data.Registry.Internal.Types Methods (==) :: ValueDescription -> ValueDescription -> Bool # (/=) :: ValueDescription -> ValueDescription -> Bool # | |
Hashable ValueDescription Source # | |
Defined in Data.Registry.Internal.Types |
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
Constructors
Function Dynamic FunctionDescription |
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
Constructors
FunctionDescription | |
Fields
|
Instances
Show FunctionDescription Source # | |
Defined in Data.Registry.Internal.Types Methods showsPrec :: Int -> FunctionDescription -> ShowS # show :: FunctionDescription -> String # showList :: [FunctionDescription] -> ShowS # | |
Eq FunctionDescription Source # | |
Defined in Data.Registry.Internal.Types Methods (==) :: 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
funDynOutTypeRep :: Function -> SomeTypeRep Source #
Type representation of the output 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
Constructors
TypedValue Value | |
TypedFunction Function |
Instances
A Untyped is used for storing either a value or a function in the registry
Constructors
UntypedValue Value | |
UntypedFunction Function |
outTypeRep :: Untyped -> SomeTypeRep Source #
Return the output type of an untyped entry
This is a list of entries in the registry available for constructing values They are sorted by output type and if there are several available functions or values for a given type the first one in the list has the highest priority
Constructors
Entries | |
Fields |
fromUntyped :: [Untyped] -> Entries Source #
Create a Entries data structure from a list of untyped entries
toFunctions :: Entries -> [Function] Source #
Create a list of functions from the Entries data structure
describeFunctions :: Entries -> Text Source #
Display a list of constructors
describeValues :: Entries -> Text Source #
Display a list of values
addUntyped :: Untyped -> Entries -> Entries Source #
Add one more Function to the list of Entries. It gets the highest priority for functions with the same output type
addEntry :: Typed a -> Entries -> Entries Source #
Add an entry to the list of Entries. It gets the highest priority for functions with the same output type
appendUntyped :: Untyped -> Entries -> Entries Source #
Add one more untyped entry to the list of Entries 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
appendEntry :: Typed a -> Entries -> Entries Source #
Add one more untyped entry to the list of Entries 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
findUntyped :: SomeTypeRep -> Entries -> Maybe Untyped Source #
Find a function or value returning a target type from a list of entries
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 | |
Fields
|
contextTypes :: Context -> [SomeTypeRep] Source #
Return the target types for a given context
newtype Dependencies Source #
The values that a value depends on
Constructors
Dependencies | |
Fields
|
Instances
Monoid Dependencies Source # | |
Defined in Data.Registry.Internal.Types Methods mempty :: Dependencies # mappend :: Dependencies -> Dependencies -> Dependencies # mconcat :: [Dependencies] -> Dependencies # | |
Semigroup Dependencies Source # | |
Defined in Data.Registry.Internal.Types Methods (<>) :: Dependencies -> Dependencies -> Dependencies # sconcat :: NonEmpty Dependencies -> Dependencies # stimes :: Integral b => b -> Dependencies -> Dependencies # | |
Show Dependencies Source # | |
Defined in Data.Registry.Internal.Types Methods showsPrec :: Int -> Dependencies -> ShowS # show :: Dependencies -> String # showList :: [Dependencies] -> ShowS # | |
Eq Dependencies Source # | |
Defined in Data.Registry.Internal.Types |
newtype DependenciesTypes Source #
The values types that a value depends on
Constructors
DependenciesTypes | |
Fields |
Instances
Monoid DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types Methods mappend :: DependenciesTypes -> DependenciesTypes -> DependenciesTypes # mconcat :: [DependenciesTypes] -> DependenciesTypes # | |
Semigroup DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types Methods (<>) :: DependenciesTypes -> DependenciesTypes -> DependenciesTypes # sconcat :: NonEmpty DependenciesTypes -> DependenciesTypes # stimes :: Integral b => b -> DependenciesTypes -> DependenciesTypes # | |
Show DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types Methods showsPrec :: Int -> DependenciesTypes -> ShowS # show :: DependenciesTypes -> String # showList :: [DependenciesTypes] -> ShowS # | |
Eq DependenciesTypes Source # | |
Defined in Data.Registry.Internal.Types Methods (==) :: DependenciesTypes -> DependenciesTypes -> Bool # (/=) :: DependenciesTypes -> DependenciesTypes -> Bool # |
dependenciesTypes :: Dependencies -> DependenciesTypes Source #
Return the types of all the dependencies
dependenciesOf :: 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
Constructors
Specializations | |
Fields |
Instances
Monoid Specializations Source # | |
Defined in Data.Registry.Internal.Types Methods mappend :: Specializations -> Specializations -> Specializations # mconcat :: [Specializations] -> Specializations # | |
Semigroup Specializations Source # | |
Defined in Data.Registry.Internal.Types Methods (<>) :: Specializations -> Specializations -> Specializations # sconcat :: NonEmpty Specializations -> Specializations # stimes :: Integral b => b -> Specializations -> Specializations # | |
Show Specializations Source # | |
Defined in Data.Registry.Internal.Types Methods 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 a target value, which is the value to use when we need a value of 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
Constructors
Specialization | |
Instances
Show Specialization Source # | |
Defined in Data.Registry.Internal.Types Methods showsPrec :: Int -> Specialization -> ShowS # show :: Specialization -> String # showList :: [Specialization] -> ShowS # |
type SpecializationPath = NonEmpty SomeTypeRep Source #
List of consecutive types used when making a specific values
See the comments on Specialization
specializedContexts :: Value -> [SpecializationContext] Source #
For each dependency of the value Return the specialization context of the value if - that dependency value is specialized - the current value is part of the context stack and part of a context path
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
Constructors
SpecializationContext | |
Fields |
Instances
Show SpecializationContext Source # | |
Defined in Data.Registry.Internal.Types Methods showsPrec :: Int -> SpecializationContext -> ShowS # show :: SpecializationContext -> String # showList :: [SpecializationContext] -> ShowS # |
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.
Constructors
SpecializationRange | |
Instances
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
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, ModifierFunction)] |
type ModifierFunction = [SpecializationContext] -> 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
createUnspecializedModifierFunction :: forall a f. (Typeable f, Typeable a, Typeable (a -> a)) => f -> ModifierFunction Source #
Create a ModifierFunction
value from a Haskell function
that will only act on unspecialized values
describeModifiers :: Modifiers -> Text Source #
Display a list of modifiers for the Registry, just showing the type of the modified value
VALUES
List of values available which can be used as parameters to constructors for building other values
Constructors
Values | |
Fields |
fromValues :: [Value] -> Values Source #
Create a Values data structure from a list of values
listValues :: Values -> [Value] Source #
Return values as a list
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 values