registry-0.2.1.0: data structure for assembling components
Safe HaskellNone
LanguageHaskell2010

Data.Registry.Solver

Description

Type level functions to statically assess if a value can be built out of a Registry

Synopsis

Documentation

type family Inputs f :: [Type] where ... Source #

Compute the list of input types for a function

Equations

Inputs (i -> o) = i ': Inputs o 
Inputs x = '[] 

type family Output f :: Type where ... Source #

Compute the output type for a function

Equations

Output (i -> o) = Output o 
Output x = x 

type family CanMake (a :: Type) (els :: [Type]) (target :: Type) :: Constraint where ... Source #

Compute if a constructor can be added to a registry

Equations

CanMake a '[] t = TypeError (((((((((((((Text "The constructor for " :$$: Text "") :$$: (Text " " :<>: ShowType (Output t))) :$$: Text "") :$$: Text "cannot be added to the registry because") :$$: Text "") :$$: (Text " " :<>: ShowType (Output a))) :$$: Text "") :$$: Text " is not one of the registry outputs") :$$: Text "") :$$: ((Text "The full constructor 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 

class IsSubset (ins :: [Type]) (out :: [Type]) (target :: Type) Source #

Compute if each element of a list of types is contained in another list

Instances

Instances details
IsSubset ('[] :: [Type]) out t Source # 
Instance details

Defined in Data.Registry.Solver

(CanMake a out t, IsSubset els out t) => IsSubset (a ': els) out t Source # 
Instance details

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

Instances details
(ts1 ~ Normalized types1, ts2 ~ Normalized types2, IsSubset ts1 ts2 (), IsSubset ts1 ts2 ()) => IsSameSet types1 types2 Source # 
Instance details

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

Equations

Contains a els = Contains1 a els els 

type family Contains1 (a :: Type) (els :: [Type]) (target :: [Type]) :: Constraint where ... Source #

Compute if a type is contained in a list of types

Equations

Contains1 a '[] target = TypeError (('ShowType a :<>: Text " cannot be found in ") :<>: 'ShowType target) 
Contains1 a (a ': els) t = () 
Contains1 a (b ': els) t = Contains1 a els t 

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

Instances details
IsSubset ins out () => Solvable ins out Source # 
Instance details

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

Equations

'[] :++ xs = xs 
(x ': xs) :++ ys = x ': (xs :++ ys) 

type family FindUnique (a :: Type) (as :: [Type]) :: [Type] where ... Source #

Return '[a] only if it is not already in the list of types

Equations

FindUnique a '[] = '[a] 
FindUnique a (a ': _rest) = '[] 
FindUnique a (_b ': rest) = FindUnique a rest 

type family Normalized (as :: [Type]) :: [Type] where ... Source #

Equations

Normalized '[] = '[] 
Normalized '[a] = '[a] 
Normalized (a ': rest) = FindUnique a rest :++ Normalized rest