syntax-tree-0.1.0.1: Typed ASTs

Safe HaskellSafe
LanguageHaskell2010

AST.Class.Foldable

Description

A variant of Foldable for Knots

Synopsis

Documentation

class KNodes k => KFoldable k where Source #

A variant of Foldable for Knots

Methods

foldMapK :: Monoid a => (forall n. KWitness k n -> Tree p n -> a) -> Tree k p -> a Source #

KFoldable variant of foldMap

Gets a function from k's nodes (trees along witnesses that they are nodes of k) into a monoid and concats its results for all nodes.

Instances
KFoldable Pure Source # 
Instance details

Defined in AST.Knot.Pure

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness Pure n -> Tree p n -> a) -> Tree Pure p -> a Source #

KFoldable Prune Source # 
Instance details

Defined in AST.Knot.Prune

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness Prune n -> Tree p n -> a) -> Tree Prune p -> a Source #

KFoldable (ANode c) Source # 
Instance details

Defined in AST.Combinator.ANode

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (ANode c) n -> Tree p n -> a) -> Tree (ANode c) p -> a Source #

Foldable f => KFoldable (F f) Source # 
Instance details

Defined in AST.Knot.Functor

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (F f) n -> Tree p n -> a) -> Tree (F f) p -> a Source #

KFoldable (Ann a) Source # 
Instance details

Defined in AST.Knot.Ann

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Ann a) n -> Tree p n -> a0) -> Tree (Ann a) p -> a0 Source #

KFoldable t => KFoldable (UnifyError t) Source # 
Instance details

Defined in AST.Unify.Error

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (UnifyError t) n -> Tree p n -> a) -> Tree (UnifyError t) p -> a Source #

KFoldable (FuncType typ) Source # 
Instance details

Defined in AST.Term.FuncType

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (FuncType typ) n -> Tree p n -> a) -> Tree (FuncType typ) p -> a Source #

(Recursively KFoldable typ, KFoldable (NomVarTypes typ)) => KFoldable (LoadedNominalDecl typ) Source # 
Instance details

Defined in AST.Term.Nominal

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (LoadedNominalDecl typ) n -> Tree p n -> a) -> Tree (LoadedNominalDecl typ) p -> a Source #

KFoldable (NominalDecl typ) Source # 
Instance details

Defined in AST.Term.Nominal

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (NominalDecl typ) n -> Tree p n -> a) -> Tree (NominalDecl typ) p -> a Source #

KFoldable (App expr) Source # 
Instance details

Defined in AST.Term.App

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (App expr) n -> Tree p n -> a) -> Tree (App expr) p -> a Source #

KFoldable (ScopeTypes t) Source # 
Instance details

Defined in AST.Term.NamelessScope

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (ScopeTypes t) n -> Tree p n -> a) -> Tree (ScopeTypes t) p -> a Source #

KFoldable (Const a :: Knot -> Type) Source # 
Instance details

Defined in AST.Class.Foldable

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Const a) n -> Tree p n -> a0) -> Tree (Const a) p -> a0 Source #

Recursively KFoldable ast => KFoldable (Flip GTerm ast) Source # 
Instance details

Defined in AST.Unify.Generalize

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (Flip GTerm ast) n -> Tree p n -> a) -> Tree (Flip GTerm ast) p -> a Source #

(Recursively KFoldable e, Recursively KFoldableInferOf e) => KFoldable (Flip (ITerm a) e) Source # 
Instance details

Defined in AST.Infer.Term

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Flip (ITerm a) e) n -> Tree p n -> a0) -> Tree (Flip (ITerm a) e) p -> a0 Source #

(Recursively KFoldable e, Recursively KFoldableInferOf e) => KFoldable (Flip (BTerm a) e) Source # 
Instance details

Defined in AST.Infer.Blame

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Flip (BTerm a) e) n -> Tree p n -> a0) -> Tree (Flip (BTerm a) e) p -> a0 Source #

(KFoldable a, KFoldable b) => KFoldable (Compose a b) Source # 
Instance details

Defined in AST.Combinator.Compose

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Compose a b) n -> Tree p n -> a0) -> Tree (Compose a b) p -> a0 Source #

KFoldable (TermMap k expr) Source # 
Instance details

Defined in AST.Term.Map

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (TermMap k expr) n -> Tree p n -> a) -> Tree (TermMap k expr) p -> a Source #

KFoldable (Var v expr) Source # 
Instance details

Defined in AST.Term.Var

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (Var v expr) n -> Tree p n -> a) -> Tree (Var v expr) p -> a Source #

KFoldable (Scheme varTypes typ) Source # 
Instance details

Defined in AST.Term.Scheme

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (Scheme varTypes typ) n -> Tree p n -> a) -> Tree (Scheme varTypes typ) p -> a Source #

KFoldable (TypeSig vars term) Source # 
Instance details

Defined in AST.Term.TypeSig

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (TypeSig vars term) n -> Tree p n -> a) -> Tree (TypeSig vars term) p -> a Source #

KFoldable (FromNom nomId term) Source # 
Instance details

Defined in AST.Term.Nominal

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (FromNom nomId term) n -> Tree p n -> a) -> Tree (FromNom nomId term) p -> a Source #

KFoldable (ToNom nomId term) Source # 
Instance details

Defined in AST.Term.Nominal

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (ToNom nomId term) n -> Tree p n -> a) -> Tree (ToNom nomId term) p -> a Source #

KFoldable v => KFoldable (NominalInst n v) Source # 
Instance details

Defined in AST.Term.Nominal

Methods

foldMapK :: Monoid a => (forall (n0 :: Knot -> Type). KWitness (NominalInst n v) n0 -> Tree p n0 -> a) -> Tree (NominalInst n v) p -> a Source #

KFoldable (Let v expr) Source # 
Instance details

Defined in AST.Term.Let

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (Let v expr) n -> Tree p n -> a) -> Tree (Let v expr) p -> a Source #

KFoldable (Lam v expr) Source # 
Instance details

Defined in AST.Term.Lam

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (Lam v expr) n -> Tree p n -> a) -> Tree (Lam v expr) p -> a Source #

KFoldable (Scope expr a) Source # 
Instance details

Defined in AST.Term.NamelessScope

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Scope expr a) n -> Tree p n -> a0) -> Tree (Scope expr a) p -> a0 Source #

KFoldable (ScopeVar expr a) Source # 
Instance details

Defined in AST.Term.NamelessScope

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (ScopeVar expr a) n -> Tree p n -> a0) -> Tree (ScopeVar expr a) p -> a0 Source #

(KFoldable a, KFoldable b) => KFoldable (Product a b) Source # 
Instance details

Defined in AST.Class.Foldable

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Product a b) n -> Tree p n -> a0) -> Tree (Product a b) p -> a0 Source #

(KFoldable a, KFoldable b) => KFoldable (Sum a b) Source # 
Instance details

Defined in AST.Class.Foldable

Methods

foldMapK :: Monoid a0 => (forall (n :: Knot -> Type). KWitness (Sum a b) n -> Tree p n -> a0) -> Tree (Sum a b) p -> a0 Source #

KFoldable (FlatRowExtends key val rest) Source # 
Instance details

Defined in AST.Term.Row

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (FlatRowExtends key val rest) n -> Tree p n -> a) -> Tree (FlatRowExtends key val rest) p -> a Source #

KFoldable (RowExtend key val rest) Source # 
Instance details

Defined in AST.Term.Row

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (RowExtend key val rest) n -> Tree p n -> a) -> Tree (RowExtend key val rest) p -> a Source #

KFoldable (TypedLam var typ expr) Source # 
Instance details

Defined in AST.Term.TypedLam

Methods

foldMapK :: Monoid a => (forall (n :: Knot -> Type). KWitness (TypedLam var typ expr) n -> Tree p n -> a) -> Tree (TypedLam var typ expr) p -> a Source #

foldMapK1 :: forall a k n p. (Monoid a, KFoldable k, KNodesConstraint k ((~) n)) => (Tree p n -> a) -> Tree k p -> a Source #

KFoldable variant for foldMap for Knots with a single node type (avoids using RankNTypes)

traverseK_ :: (Applicative f, KFoldable k) => (forall c. KWitness k c -> Tree m c -> f ()) -> Tree k m -> f () Source #

KFoldable variant of traverse_

Applise a given action on all subtrees (represented as trees along witnesses that they are nodes of k)

traverseK1_ :: forall f k n p. (Applicative f, KFoldable k, KNodesConstraint k ((~) n)) => (Tree p n -> f ()) -> Tree k p -> f () Source #

KFoldable variant of traverse_ for Knots with a single node type (avoids using RankNTypes)