hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Class.Foldable

Description

A variant of Foldable for HyperTypes

Synopsis

Documentation

class HNodes h => HFoldable h where Source #

A variant of Foldable for HyperTypes

Minimal complete definition

Nothing

Methods

hfoldMap :: Monoid a => (forall n. HWitness h n -> (p # n) -> a) -> (h # p) -> a Source #

HFoldable variant of foldMap

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

default hfoldMap :: (Generic1 h, HFoldable (Rep1 h), HWitnessType h ~ HWitnessType (Rep1 h), Monoid a) => (forall n. HWitness h n -> (p # n) -> a) -> (h # p) -> a Source #

Instances

Instances details
HFoldable Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness Prune n -> (p # n) -> a) -> (Prune # p) -> a Source #

HFoldable Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness Pure n -> (p # n) -> a) -> (Pure # p) -> a Source #

HFoldable (ANode c) Source # 
Instance details

Defined in Hyper.Combinator.ANode

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (ANode c) n -> (p # n) -> a) -> (ANode c # p) -> a Source #

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

Defined in Hyper.Combinator.Ann

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (Ann a) n -> (p # n) -> a0) -> (Ann a # p) -> a0 Source #

HFoldable (App expr) Source # 
Instance details

Defined in Hyper.Syntax.App

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (App expr) n -> (p # n) -> a) -> (App expr # p) -> a Source #

HFoldable (FuncType typ) Source # 
Instance details

Defined in Hyper.Syntax.FuncType

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (FuncType typ) n -> (p # n) -> a) -> (FuncType typ # p) -> a Source #

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

Defined in Hyper.Syntax.Nominal

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (LoadedNominalDecl typ) n -> (p # n) -> a) -> (LoadedNominalDecl typ # p) -> a Source #

HFoldable (NominalDecl typ) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (NominalDecl typ) n -> (p # n) -> a) -> (NominalDecl typ # p) -> a Source #

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

Defined in Hyper.Type.Functor

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (F f) n -> (p # n) -> a) -> (F f # p) -> a Source #

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

Defined in Hyper.Unify.Error

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (UnifyError t) n -> (p # n) -> a) -> (UnifyError t # p) -> a Source #

HFoldable v => HFoldable (GTerm v) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (GTerm v) n -> (p # n) -> a) -> (GTerm v # p) -> a Source #

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

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (Const a) n -> (p # n) -> a0) -> (Const a # p) -> a0 Source #

HFoldable h => HFoldable (Rec1 h) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Rec1 h) n -> (p # n) -> a) -> (Rec1 h # p) -> a Source #

(HFoldable a, HFoldable b) => HFoldable (HCompose a b) Source # 
Instance details

Defined in Hyper.Combinator.Compose

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (HCompose a b) n -> (p # n) -> a0) -> (HCompose a b # p) -> a0 Source #

Recursively HFoldable h => HFoldable (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Combinator.Ann

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (HFlip Ann h) n -> (p # n) -> a) -> (HFlip Ann h # p) -> a Source #

HFoldable (InferOf e) => HFoldable (HFlip InferResult e) Source # 
Instance details

Defined in Hyper.Infer.Result

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (HFlip InferResult e) n -> (p # n) -> a) -> (HFlip InferResult e # p) -> a Source #

Recursively HFoldable ast => HFoldable (HFlip GTerm ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (HFlip GTerm ast) n -> (p # n) -> a) -> (HFlip GTerm ast # p) -> a Source #

HFoldable (Lam v expr) Source # 
Instance details

Defined in Hyper.Syntax.Lam

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Lam v expr) n -> (p # n) -> a) -> (Lam v expr # p) -> a Source #

HFoldable (Let v expr) Source # 
Instance details

Defined in Hyper.Syntax.Let

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Let v expr) n -> (p # n) -> a) -> (Let v expr # p) -> a Source #

HFoldable (TermMap h expr) Source # 
Instance details

Defined in Hyper.Syntax.Map

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (TermMap h expr) n -> (p # n) -> a) -> (TermMap h expr # p) -> a Source #

HFoldable (FromNom nomId term) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (FromNom nomId term) n -> (p # n) -> a) -> (FromNom nomId term # p) -> a Source #

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

Defined in Hyper.Syntax.Nominal

Methods

hfoldMap :: Monoid a => (forall (n0 :: HyperType). HWitness (NominalInst n v) n0 -> (p # n0) -> a) -> (NominalInst n v # p) -> a Source #

HFoldable (ToNom nomId term) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (ToNom nomId term) n -> (p # n) -> a) -> (ToNom nomId term # p) -> a Source #

HFoldable (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Scheme varTypes typ) n -> (p # n) -> a) -> (Scheme varTypes typ # p) -> a Source #

HFoldable (TypeSig vars term) Source # 
Instance details

Defined in Hyper.Syntax.TypeSig

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (TypeSig vars term) n -> (p # n) -> a) -> (TypeSig vars term # p) -> a Source #

HFoldable (Var v expr) Source # 
Instance details

Defined in Hyper.Syntax.Var

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Var v expr) n -> (p # n) -> a) -> (Var v expr # p) -> a Source #

(HFoldable a, HFoldable b) => HFoldable (a :*: b) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (a :*: b) n -> (p # n) -> a0) -> ((a :*: b) # p) -> a0 Source #

(HFoldable a, HFoldable b) => HFoldable (a :+: b) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a0 => (forall (n :: HyperType). HWitness (a :+: b) n -> (p # n) -> a0) -> ((a :+: b) # p) -> a0 Source #

HFoldable (FlatRowExtends key val rest) Source # 
Instance details

Defined in Hyper.Syntax.Row

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (FlatRowExtends key val rest) n -> (p # n) -> a) -> (FlatRowExtends key val rest # p) -> a Source #

HFoldable (RowExtend key val rest) Source # 
Instance details

Defined in Hyper.Syntax.Row

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (RowExtend key val rest) n -> (p # n) -> a) -> (RowExtend key val rest # p) -> a Source #

HFoldable (TypedLam var typ expr) Source # 
Instance details

Defined in Hyper.Syntax.TypedLam

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (TypedLam var typ expr) n -> (p # n) -> a) -> (TypedLam var typ expr # p) -> a Source #

HFoldable h => HFoldable (M1 i m h) Source # 
Instance details

Defined in Hyper.Class.Foldable

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (M1 i m h) n -> (p # n) -> a) -> (M1 i m h # p) -> a Source #

hfolded1 :: forall h n p. (HFoldable h, HNodesConstraint h ((~) n)) => Fold (h # p) (p # n) Source #

HFoldable variant for folded for HyperTypes with a single node type.

Avoids using RankNTypes and thus can be composed with other optics.

htraverse_ :: (Applicative f, HFoldable h) => (forall c. HWitness h c -> (m # c) -> f ()) -> (h # m) -> f () Source #

HFoldable variant of traverse_

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

htraverse1_ :: forall f h n p. (Applicative f, HFoldable h, HNodesConstraint h ((~) n)) => ((p # n) -> f ()) -> (h # p) -> f () Source #

HFoldable variant of traverse_ for HyperTypes with a single node type (avoids using RankNTypes)