Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Type level functions to statically assess if a value can be built out of a Registry
Synopsis
- type family Inputs f :: [Type] where ...
- type family Output f :: Type where ...
- type family CanMake (a :: Type) (els :: [Type]) (target :: Type) :: Constraint where ...
- type family CanMakeMany (a :: Type) (els :: [Type]) (targets :: [Type]) :: Constraint where ...
- class IsSubset (ins :: [Type]) (out :: [Type]) (target :: Type)
- class AreSubset (ins :: [Type]) (out :: [Type]) (targets :: [Type])
- class IsSameSet (types1 :: [Type]) (types2 :: [Type])
- type family Contains (a :: Type) (els :: [Type]) :: Constraint where ...
- type family Contains1 (a :: Type) (els :: [Type]) (target :: [Type]) :: Constraint where ...
- type (:-) out a = Contains a out
- class Solvable (ins :: [Type]) (out :: [Type])
- type family (x :: [k]) :++ (y :: [k]) :: [k] where ...
- type family FindUnique (a :: Type) (as :: [Type]) :: [Type] where ...
- type family Normalized (as :: [Type]) :: [Type] where ...
Documentation
type family CanMake (a :: Type) (els :: [Type]) (target :: Type) :: Constraint where ... Source #
Compute if a function can be added to a registry
CanMake a '[] t = TypeError (((((((((((((Text "The function creating the output type " :$$: Text "") :$$: (Text " " :<>: ShowType (Output t))) :$$: Text "") :$$: Text "cannot be added to the registry because the input parameter") :$$: Text "") :$$: (Text " " :<>: ShowType (Output a))) :$$: Text "") :$$: Text " is not one of the registry outputs") :$$: Text "") :$$: ((Text "The full function type for " :<>: ShowType (Output t)) :<>: Text " is")) :$$: Text "") :$$: ShowType t) :$$: Text "") | |
CanMake a (a ': _els) _t = () | |
CanMake a (_b ': els) t = CanMake a els t |
type family CanMakeMany (a :: Type) (els :: [Type]) (targets :: [Type]) :: Constraint where ... Source #
Compute if a registry can be added to another registry
CanMakeMany a '[] ts = TypeError (((((((((Text "The registry creating the output types " :$$: Text "") :$$: (Text " " :<>: ShowType ts)) :$$: Text "") :$$: Text "cannot be added to the other registry because one input parameter") :$$: Text "") :$$: (Text " " :<>: ShowType (Output a))) :$$: Text "") :$$: Text " is missing of the overall registry outputs") :$$: Text "") | |
CanMakeMany a (a ': _els) _ts = () | |
CanMakeMany a (_b ': els) ts = CanMakeMany a els ts |
class IsSubset (ins :: [Type]) (out :: [Type]) (target :: Type) Source #
Compute if each element of a list of types is contained in another list
when trying to add the function target
Instances
IsSubset ('[] :: [Type]) out t Source # | |
Defined in Data.Registry.Solver | |
(CanMake a out t, IsSubset els out t) => IsSubset (a ': els) out t Source # | The list of elements: a + els is a subset of out if els is a subset of out and a is also included in the set out. The search for a in out is done via a type family in order to be able to display an error message if it can't be found |
Defined in Data.Registry.Solver |
class AreSubset (ins :: [Type]) (out :: [Type]) (targets :: [Type]) Source #
Compute if each element of a list of types is contained in
another list when trying to append 2 registries together
where target
is the list of inputs of the first registry
Instances
AreSubset ('[] :: [Type]) out ts Source # | |
Defined in Data.Registry.Solver | |
(CanMakeMany a out ts, AreSubset els out ts) => AreSubset (a ': els) out ts Source # | |
Defined in Data.Registry.Solver |
class IsSameSet (types1 :: [Type]) (types2 :: [Type]) Source #
Compute if each element of a list of types is the same as another in a different order
Instances
(ts1 ~ Normalized types1, ts2 ~ Normalized types2, IsSubset ts1 ts2 (), IsSubset ts1 ts2 ()) => IsSameSet types1 types2 Source # | |
Defined in Data.Registry.Solver |
type family Contains (a :: Type) (els :: [Type]) :: Constraint where ... Source #
Compute if a type is contained in a list of types
type family Contains1 (a :: Type) (els :: [Type]) (target :: [Type]) :: Constraint where ... Source #
Compute if a type is contained in a list of types
type (:-) out a = Contains a out Source #
Shorthand type alias when many such constraints need to be added to a type signature
class Solvable (ins :: [Type]) (out :: [Type]) Source #
From the list of all the input types and outputs types of a registry Can we create all the output types?
Instances
IsSubset ins out () => Solvable ins out Source # | |
Defined in Data.Registry.Solver |
type family (x :: [k]) :++ (y :: [k]) :: [k] where ... Source #
Extracted from the typelevel-sets project and adapted for the Registry datatype This union deduplicates elements only if they appear in contiguously What we really want is typelevel sets but they are too slow for now https://github.com/dorchard/type-level-sets/issues/17
type family FindUnique (a :: Type) (as :: [Type]) :: [Type] where ... Source #
Return '[a] only if it is not already in the list of types
FindUnique a '[] = '[a] | |
FindUnique a (a ': _rest) = '[] | |
FindUnique a (_b ': rest) = FindUnique a rest |
type family Normalized (as :: [Type]) :: [Type] where ... Source #
Type family to remove some redundant types in a list of types
Normalized '[] = '[] | |
Normalized '[a] = '[a] | |
Normalized (a ': rest) = FindUnique a rest :++ Normalized rest |