htree-0.1.1.0: An implemementation of a heterogeneous rosetree
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.HTree.Families

Description

generic types and type families used in some of the modules

Synopsis
  • type family All c xs where ...
  • class All c xs => AllC c xs
  • class AllInv l k
  • class (c1 a, c2 a) => Both c1 c2 a
  • type family Not a where ...
  • class Top k
  • type family xs ++ ys where ...
  • type family a || b where ...

Documentation

type family All c xs where ... Source #

for all elements of a list, a contraint holds

Equations

All c '[] = () 
All c (x : xs) = (c x, All c xs) 

class All c xs => AllC c xs Source #

like All but can be partially applied

Instances

Instances details
All c xs => AllC (c :: k -> Constraint) (xs :: [k]) Source # 
Instance details

Defined in Data.HTree.Families

class AllInv l k Source #

All but inversed: holds if all constraints in the list hold

Instances

Instances details
AllInv ('[] :: [k1 -> Constraint]) (k2 :: k1) Source # 
Instance details

Defined in Data.HTree.Families

(c k2, AllInv cs k2) => AllInv (c ': cs :: [k1 -> Constraint]) (k2 :: k1) Source # 
Instance details

Defined in Data.HTree.Families

class (c1 a, c2 a) => Both c1 c2 a Source #

product of two classes

Instances

Instances details
(c1 a, c2 a) => Both (c1 :: k -> Constraint) (c2 :: k -> Constraint) (a :: k) Source # 
Instance details

Defined in Data.HTree.Families

(forall x. Eq x => Eq (f x), Typeable f) => Eq (EList (Has (Both (Typeable :: Type -> Constraint) Eq) f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: EList (Has (Both Typeable Eq) f) -> EList (Has (Both Typeable Eq) f) -> Bool #

(/=) :: EList (Has (Both Typeable Eq) f) -> EList (Has (Both Typeable Eq) f) -> Bool #

(forall x. Eq x => Eq (f x), Typeable f) => Eq (ETree (Has (Both (Typeable :: Type -> Constraint) Eq) f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: ETree (Has (Both Typeable Eq) f) -> ETree (Has (Both Typeable Eq) f) -> Bool #

(/=) :: ETree (Has (Both Typeable Eq) f) -> ETree (Has (Both Typeable Eq) f) -> Bool #

type family Not a where ... Source #

like not but on the type level

Equations

Not 'True = 'False 
Not 'False = 'True 

class Top k Source #

the class that every type has an instance for

Instances

Instances details
Top (k2 :: k1) Source # 
Instance details

Defined in Data.HTree.Families

type family xs ++ ys where ... infixr 5 Source #

like (++) on the value level but on the type level

Equations

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

type family a || b where ... Source #

typelevel Or

Equations

'True || b = 'True 
'False || b = b