hypertypes-0.1.0.2: Typed ASTs
Safe HaskellNone
LanguageHaskell2010

Hyper.Class.Recursive

Description

Classes applying on HyperTypes recursively

Synopsis

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

Instances details
Recursive RTraversable Source # 
Instance details

Defined in Hyper.Class.Recursive

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, RTraversable h) => proxy (RTraversable h) -> Dict (HNodesConstraint h RTraversable) Source #

Recursive RNodes Source # 
Instance details

Defined in Hyper.Class.Recursive

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, RNodes h) => proxy (RNodes h) -> Dict (HNodesConstraint h RNodes) Source #

Recursive RTraversableInferOf Source # 
Instance details

Defined in Hyper.Class.Infer.InferOf

Recursive (Recursively c) Source # 
Instance details

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 (UnifyGen m) Source # 
Instance details

Defined in Hyper.Class.Unify

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, UnifyGen m h) => proxy (UnifyGen m h) -> Dict (HNodesConstraint h (UnifyGen m)) Source #

Recursive (Unify m) Source # 
Instance details

Defined in Hyper.Class.Unify

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, Unify m h) => proxy (Unify m h) -> Dict (HNodesConstraint h (Unify m)) Source #

Recursive (Infer m) Source # 
Instance details

Defined in Hyper.Class.Infer

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, Infer m h) => proxy (Infer m h) -> Dict (HNodesConstraint h (Infer m)) Source #

Recursive (Blame m) Source # 
Instance details

Defined in Hyper.Infer.Blame

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, Blame m h) => proxy (Blame m h) -> Dict (HNodesConstraint h (Blame m)) Source #

Recursive (HasScheme varTypes m) Source # 
Instance details

Defined in Hyper.Type.AST.Scheme

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, HasScheme varTypes m h) => proxy (HasScheme varTypes m h) -> Dict (HNodesConstraint h (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

Instances details
c Pure => Recursively c Pure Source # 
Instance details

Defined in Hyper.Class.Recursive

c Prune => Recursively c Prune Source # 
Instance details

Defined in Hyper.Type.Prune

(c (Ann a), Recursively c a) => Recursively c (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

recursively :: proxy (c (Ann a)) -> Dict (c (Ann a), HNodesConstraint (Ann a) (Recursively c)) Source #

(c (ANode n), Recursively c n) => Recursively c (ANode n) Source # 
Instance details

Defined in Hyper.Combinator.ANode

Methods

recursively :: proxy (c (ANode n)) -> Dict (c (ANode n), HNodesConstraint (ANode n) (Recursively c)) Source #

c (F f) => Recursively c (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

recursively :: proxy (c (F f)) -> Dict (c (F f), HNodesConstraint (F f) (Recursively c)) Source #

(c (App e), Recursively c e) => Recursively c (App e) Source # 
Instance details

Defined in Hyper.Type.AST.App

Methods

recursively :: proxy (c (App e)) -> Dict (c (App e), HNodesConstraint (App e) (Recursively c)) Source #

c (Const a :: AHyperType -> Type) => Recursively c (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Recursive

Methods

recursively :: proxy (c (Const a)) -> Dict (c (Const a), HNodesConstraint (Const a) (Recursively c)) Source #

(HNodes h0, HNodes h1, c (HCompose h0 h1), HNodesConstraint h0 (HComposeConstraint0 RNodes h1), HNodesConstraint h0 (HComposeConstraint0 (Recursively c) h1)) => Recursively c (HCompose h0 h1) Source # 
Instance details

Defined in Hyper.Combinator.Compose

Methods

recursively :: proxy (c (HCompose h0 h1)) -> Dict (c (HCompose h0 h1), HNodesConstraint (HCompose h0 h1) (Recursively c)) Source #

(c (Scheme v t), Recursively c t) => Recursively c (Scheme v t) Source # 
Instance details

Defined in Hyper.Type.AST.Scheme

Methods

recursively :: proxy (c (Scheme v t)) -> Dict (c (Scheme v t), HNodesConstraint (Scheme v t) (Recursively c)) Source #

(c (Lam v t), Recursively c t) => Recursively c (Lam v t) Source # 
Instance details

Defined in Hyper.Type.AST.Lam

Methods

recursively :: proxy (c (Lam v t)) -> Dict (c (Lam v t), HNodesConstraint (Lam v t) (Recursively c)) Source #

(c (TypedLam v t e), Recursively c t, Recursively c e) => Recursively c (TypedLam v t e) Source # 
Instance details

Defined in Hyper.Type.AST.TypedLam

Methods

recursively :: proxy (c (TypedLam v t e)) -> Dict (c (TypedLam v t e), HNodesConstraint (TypedLam v t e) (Recursively c)) Source #

Recursive (Recursively c) Source # 
Instance details

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 #

class HNodes h => RNodes h where Source #

A class of HyperTypes which recursively implement HNodes

Minimal complete definition

Nothing

Instances

Instances details
RNodes Pure Source # 
Instance details

Defined in Hyper.Class.Recursive

RNodes Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Recursive RNodes Source # 
Instance details

Defined in Hyper.Class.Recursive

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, RNodes h) => proxy (RNodes h) -> Dict (HNodesConstraint h RNodes) Source #

RNodes a => RNodes (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

recursiveHNodes :: proxy (Ann a) -> Dict (HNodesConstraint (Ann a) RNodes) Source #

RNodes n => RNodes (ANode n) Source # 
Instance details

Defined in Hyper.Combinator.ANode

RNodes (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

recursiveHNodes :: proxy (F f) -> Dict (HNodesConstraint (F f) RNodes) Source #

RNodes e => RNodes (App e) Source # 
Instance details

Defined in Hyper.Type.AST.App

Methods

recursiveHNodes :: proxy (App e) -> Dict (HNodesConstraint (App e) RNodes) Source #

RNodes (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Recursive

(HNodes a, HNodes b, HNodesConstraint a (HComposeConstraint0 RNodes b)) => RNodes (HCompose a b) Source # 
Instance details

Defined in Hyper.Combinator.Compose

RNodes t => RNodes (Scheme v t) Source # 
Instance details

Defined in Hyper.Type.AST.Scheme

Methods

recursiveHNodes :: proxy (Scheme v t) -> Dict (HNodesConstraint (Scheme v t) RNodes) Source #

RNodes t => RNodes (Lam v t) Source # 
Instance details

Defined in Hyper.Type.AST.Lam

Methods

recursiveHNodes :: proxy (Lam v t) -> Dict (HNodesConstraint (Lam v t) RNodes) Source #

(RNodes t, RNodes e) => RNodes (TypedLam v t e) Source # 
Instance details

Defined in Hyper.Type.AST.TypedLam

Methods

recursiveHNodes :: proxy (TypedLam v t e) -> Dict (HNodesConstraint (TypedLam v t e) RNodes) Source #

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

Instances

Instances details
RTraversable Pure Source # 
Instance details

Defined in Hyper.Class.Recursive

RTraversable Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Recursive RTraversable Source # 
Instance details

Defined in Hyper.Class.Recursive

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, RTraversable h) => proxy (RTraversable h) -> Dict (HNodesConstraint h RTraversable) Source #

RTraversable a => RTraversable (Ann a) Source # 
Instance details

Defined in Hyper.Combinator.Ann

RTraversable n => RTraversable (ANode n) Source # 
Instance details

Defined in Hyper.Combinator.ANode

Traversable f => RTraversable (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

RTraversable e => RTraversable (App e) Source # 
Instance details

Defined in Hyper.Type.AST.App

RTraversable (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Recursive

(HTraversable a, HTraversable b, HNodesConstraint a (HComposeConstraint0 RNodes b), HNodesConstraint a (HComposeConstraint0 (Recursively HFunctor) b), HNodesConstraint a (HComposeConstraint0 (Recursively HFoldable) b), HNodesConstraint a (HComposeConstraint0 RTraversable b)) => RTraversable (HCompose a b) Source # 
Instance details

Defined in Hyper.Combinator.Compose

(HTraversable (Scheme v t), RTraversable t) => RTraversable (Scheme v t) Source # 
Instance details

Defined in Hyper.Type.AST.Scheme

RTraversable t => RTraversable (Lam v t) Source # 
Instance details

Defined in Hyper.Type.AST.Lam

(RTraversable t, RTraversable e) => RTraversable (TypedLam v t e) Source # 
Instance details

Defined in Hyper.Type.AST.TypedLam

proxyArgument :: proxy (f h :: Constraint) -> Proxy (h :: HyperType) Source #

Helper Proxy combinator that is useful in many instances of Recursive