Safe Haskell | None |
---|---|
Language | GHC2021 |
Data.HTree.Families
Description
generic types and type families used in some of the modules
Synopsis
- type family All (c :: k -> Constraint) (xs :: [k]) where ...
- class All c xs => AllC (c :: k -> Constraint) (xs :: [k])
- class AllInv (l :: [k -> Constraint]) (k1 :: k)
- class (c1 a, c2 a) => Both (c1 :: k -> Constraint) (c2 :: k -> Constraint) (a :: k)
- type family Not (a :: Bool) :: Bool where ...
- class Top (k1 :: k)
- type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ...
- type family (a :: Bool) || (b :: Bool) :: Bool where ...
Documentation
type family All (c :: k -> Constraint) (xs :: [k]) where ... Source #
for all elements of a list, a contraint holds
Equations
All (c :: k -> Constraint) ('[] :: [k]) = () | |
All (c :: k -> Constraint) (x ': xs :: [k]) = (c x, All c xs) |
class All c xs => AllC (c :: k -> Constraint) (xs :: [k]) Source #
like All but can be partially applied
Instances
All c xs => AllC (c :: k -> Constraint) (xs :: [k]) Source # | |
Defined in Data.HTree.Families |
class AllInv (l :: [k -> Constraint]) (k1 :: k) Source #
All
but inversed: holds if all constraints in the list hold
Instances
AllInv ('[] :: [k1 -> Constraint]) (k2 :: k1) Source # | |
Defined in Data.HTree.Families | |
(c k2, AllInv cs k2) => AllInv (c ': cs :: [k1 -> Constraint]) (k2 :: k1) Source # | |
Defined in Data.HTree.Families |
class (c1 a, c2 a) => Both (c1 :: k -> Constraint) (c2 :: k -> Constraint) (a :: k) Source #
product of two classes
Instances
(c1 a, c2 a) => Both (c1 :: k -> Constraint) (c2 :: k -> Constraint) (a :: k) Source # | |
Defined in Data.HTree.Families |
the class that every type has an instance for
Instances
Top (k2 :: k1) Source # | |
Defined in Data.HTree.Families |