Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
A class for lifting constraints to child nodes of a Knot
.
Synopsis
- class KNodes (k :: Knot -> Type) where
- type KNodesConstraint k (c :: (Knot -> Type) -> Constraint) :: Constraint
- data KWitness k :: (Knot -> Type) -> Type
- kLiftConstraint :: KNodesConstraint k c => KWitness k n -> Proxy c -> (c n => r) -> r
- (#>) :: (KNodes k, KNodesConstraint k c) => Proxy c -> (c n => r) -> KWitness k n -> r
- (#*#) :: (KNodes k, KNodesConstraint k c) => Proxy c -> (KWitness k n -> c n => r) -> KWitness k n -> r
Documentation
class KNodes (k :: Knot -> Type) where Source #
KNodes
allows lifting a constraint to the child nodes of a Knot
by using the KNodesConstraint
type family.
It also provides some methods to combine and process child node constraints.
Various classes like KFunctor
build upon KNodes
to provide methods such as mapKWith
which provide a rank-n function
for processing child nodes which requires a constraint on the nodes.
type KNodesConstraint k (c :: (Knot -> Type) -> Constraint) :: Constraint Source #
Lift a constraint to apply to the child nodes
data KWitness k :: (Knot -> Type) -> Type Source #
KWitness k n
is a witness that n
is a node of k
kLiftConstraint :: KNodesConstraint k c => KWitness k n -> Proxy c -> (c n => r) -> r Source #
Lift a rank-n value with a constraint which the child nodes satisfy to a function from a node witness.