hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Class.Pointed

Description

A variant of Pointed for HyperTypes

Synopsis

Documentation

class HNodes h => HPointed h where Source #

A variant of Pointed for HyperTypes

Methods

hpure :: (forall n. HWitness h n -> p # n) -> h # p Source #

Construct a value from a generator of h's nodes (a generator which can generate a tree of any type given a witness that it is a node of h)

Instances

Instances details
HPointed Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

hpure :: (forall (n :: HyperType). HWitness Prune n -> p # n) -> Prune # p Source #

HPointed Pure Source # 
Instance details

Defined in Hyper.Type.Pure

Methods

hpure :: (forall (n :: HyperType). HWitness Pure n -> p # n) -> Pure # p Source #

HPointed (ANode c) Source # 
Instance details

Defined in Hyper.Combinator.ANode

Methods

hpure :: (forall (n :: HyperType). HWitness (ANode c) n -> p # n) -> ANode c # p Source #

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

Defined in Hyper.Combinator.Ann

Methods

hpure :: (forall (n :: HyperType). HWitness (Ann a) n -> p # n) -> Ann a # p Source #

HPointed (App expr) Source # 
Instance details

Defined in Hyper.Syntax.App

Methods

hpure :: (forall (n :: HyperType). HWitness (App expr) n -> p # n) -> App expr # p Source #

HPointed (FuncType typ) Source # 
Instance details

Defined in Hyper.Syntax.FuncType

Methods

hpure :: (forall (n :: HyperType). HWitness (FuncType typ) n -> p # n) -> FuncType typ # p Source #

Applicative f => HPointed (F f) Source # 
Instance details

Defined in Hyper.Type.Functor

Methods

hpure :: (forall (n :: HyperType). HWitness (F f) n -> p # n) -> F f # p Source #

Monoid a => HPointed (Const a :: AHyperType -> Type) Source # 
Instance details

Defined in Hyper.Class.Pointed

Methods

hpure :: (forall (n :: HyperType). HWitness (Const a) n -> p # n) -> Const a # p Source #

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

Defined in Hyper.Combinator.Compose

Methods

hpure :: (forall (n :: HyperType). HWitness (HCompose a b) n -> p # n) -> HCompose a b # p Source #

Monoid v => HPointed (Lam v expr) Source # 
Instance details

Defined in Hyper.Syntax.Lam

Methods

hpure :: (forall (n :: HyperType). HWitness (Lam v expr) n -> p # n) -> Lam v expr # p Source #

Monoid v => HPointed (Let v expr) Source # 
Instance details

Defined in Hyper.Syntax.Let

Methods

hpure :: (forall (n :: HyperType). HWitness (Let v expr) n -> p # n) -> Let v expr # p Source #

Applicative (Map h) => HPointed (TermMap h expr) Source # 
Instance details

Defined in Hyper.Syntax.Map

Methods

hpure :: (forall (n :: HyperType). HWitness (TermMap h expr) n -> p # n) -> TermMap h expr # p Source #

Monoid nomId => HPointed (FromNom nomId term) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hpure :: (forall (n :: HyperType). HWitness (FromNom nomId term) n -> p # n) -> FromNom nomId term # p Source #

Monoid nomId => HPointed (ToNom nomId term) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hpure :: (forall (n :: HyperType). HWitness (ToNom nomId term) n -> p # n) -> ToNom nomId term # p Source #

Monoid (varTypes # QVars) => HPointed (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

hpure :: (forall (n :: HyperType). HWitness (Scheme varTypes typ) n -> p # n) -> Scheme varTypes typ # p Source #

HPointed (TypeSig vars term) Source # 
Instance details

Defined in Hyper.Syntax.TypeSig

Methods

hpure :: (forall (n :: HyperType). HWitness (TypeSig vars term) n -> p # n) -> TypeSig vars term # p Source #

Monoid v => HPointed (Var v expr) Source # 
Instance details

Defined in Hyper.Syntax.Var

Methods

hpure :: (forall (n :: HyperType). HWitness (Var v expr) n -> p # n) -> Var v expr # p Source #

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

Defined in Hyper.Class.Pointed

Methods

hpure :: (forall (n :: HyperType). HWitness (a :*: b) n -> p # n) -> (a :*: b) # p Source #

Applicative (Map key) => HPointed (FlatRowExtends key val rest) Source # 
Instance details

Defined in Hyper.Syntax.Row

Methods

hpure :: (forall (n :: HyperType). HWitness (FlatRowExtends key val rest) n -> p # n) -> FlatRowExtends key val rest # p Source #

Monoid key => HPointed (RowExtend key val rest) Source # 
Instance details

Defined in Hyper.Syntax.Row

Methods

hpure :: (forall (n :: HyperType). HWitness (RowExtend key val rest) n -> p # n) -> RowExtend key val rest # p Source #

Monoid var => HPointed (TypedLam var typ expr) Source # 
Instance details

Defined in Hyper.Syntax.TypedLam

Methods

hpure :: (forall (n :: HyperType). HWitness (TypedLam var typ expr) n -> p # n) -> TypedLam var typ expr # p Source #