| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hyper.Class.Recursive
Description
Classes applying on HyperTypes recursively
Synopsis
- class Recursive c where
- recurse :: (HNodes h, c h) => proxy (c h) -> Dict (HNodesConstraint h c)
- class RNodes h => Recursively c h where
- recursively :: proxy (c h) -> Dict (c h, HNodesConstraint h (Recursively c))
- class HNodes h => RNodes h where
- class (HTraversable h, Recursively HFunctor h, Recursively HFoldable h) => RTraversable h where
- type RecMethod c h = Proxy h -> Dict (HNodesConstraint h c)
- type DefRecMethod c h = HNodesConstraint h c => RecMethod c h
- proxyArgument :: proxy (f h :: Constraint) -> Proxy (h :: HyperType)
Documentation
class Recursive c where Source #
A class of constraint constructors that apply to all recursive child nodes
Methods
recurse :: (HNodes h, c h) => proxy (c h) -> Dict (HNodesConstraint h c) Source #
Lift a recursive constraint to the next layer
Instances
| Recursive RNodes Source # | |
| Recursive RTraversable Source # | |
Defined in Hyper.Class.Recursive Methods recurse :: forall (h :: HyperType) proxy. (HNodes h, RTraversable h) => proxy (RTraversable h) -> Dict (HNodesConstraint h RTraversable) Source # | |
| Recursive (Infer m) Source # | |
| Recursive (Recursively c) Source # | |
Defined in Hyper.Class.Recursive Methods recurse :: forall (h :: HyperType) proxy. (HNodes h, Recursively c h) => proxy (Recursively c h) -> Dict (HNodesConstraint h (Recursively c)) Source # | |
| Recursive (Unify m) Source # | |
| Recursive (UnifyGen m) Source # | |
| Recursive (Blame m) Source # | |
| Recursive (HasScheme varTypes m) Source # | |
class RNodes h => Recursively c h where Source #
A constraint lifted to apply recursively.
Note that in cases where a constraint has dependencies other than RNodes,
one will want to create a class such as RTraversable to capture the dependencies,
otherwise using it in class contexts will be quite unergonomic.
Minimal complete definition
Nothing
Methods
recursively :: proxy (c h) -> Dict (c h, HNodesConstraint h (Recursively c)) Source #
default recursively :: (c h, HNodesConstraint h (Recursively c)) => proxy (c h) -> Dict (c h, HNodesConstraint h (Recursively c)) Source #
Instances
class HNodes h => RNodes h where Source #
Minimal complete definition
Nothing
Methods
recursiveHNodes :: RecMethod RNodes h Source #
default recursiveHNodes :: DefRecMethod RNodes h Source #
Instances
| RNodes Prune Source # | |
Defined in Hyper.Type.Prune | |
| RNodes Pure Source # | |
Defined in Hyper.Class.Recursive | |
| Recursive RNodes Source # | |
| RNodes n => RNodes (ANode n) Source # | |
Defined in Hyper.Combinator.ANode | |
| RNodes a => RNodes (Ann a) Source # | |
Defined in Hyper.Combinator.Ann | |
| RNodes e => RNodes (App e) Source # | |
Defined in Hyper.Syntax.App | |
| RNodes (F f) Source # | |
Defined in Hyper.Type.Functor | |
| RNodes (Const a :: AHyperType -> Type) Source # | |
Defined in Hyper.Class.Recursive | |
| (HNodes a, HNodes b, HNodesConstraint a (HComposeConstraint0 RNodes b)) => RNodes (HCompose a b) Source # | |
Defined in Hyper.Combinator.Compose | |
| RNodes t => RNodes (Lam v t) Source # | |
Defined in Hyper.Syntax.Lam | |
| RNodes t => RNodes (Scheme v t) Source # | |
Defined in Hyper.Syntax.Scheme | |
| (RNodes t, RNodes e) => RNodes (TypedLam v t e) Source # | |
Defined in Hyper.Syntax.TypedLam | |
class (HTraversable h, Recursively HFunctor h, Recursively HFoldable h) => RTraversable h where Source #
A class of HyperTypes which recursively implement HTraversable
Minimal complete definition
Nothing
Methods
recursiveHTraversable :: RecMethod RTraversable h Source #
default recursiveHTraversable :: DefRecMethod RTraversable h Source #
Instances
type DefRecMethod c h = HNodesConstraint h c => RecMethod c h Source #
proxyArgument :: proxy (f h :: Constraint) -> Proxy (h :: HyperType) Source #
Helper Proxy combinator that is useful in many instances of Recursive