hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Class.Context

Synopsis

Documentation

class HContext h where Source #

Methods

hcontext :: (h # p) -> h # (HFunc p (Const (h # p)) :*: p) Source #

Add next to each node a function to replace it in the parent with a different value

Instances

Instances details
HContext Prune Source # 
Instance details

Defined in Hyper.Type.Prune

Methods

hcontext :: forall (p :: HyperType). (Prune # p) -> Prune # (HFunc p (Const (Prune # p)) :*: p) Source #

HContext Pure Source # 
Instance details

Defined in Hyper.Class.Context

Methods

hcontext :: forall (p :: HyperType). (Pure # p) -> Pure # (HFunc p (Const (Pure # p)) :*: p) Source #

(HContext a, HFunctor a) => HContext (Ann a) Source # 
Instance details

Defined in Hyper.Class.Context

Methods

hcontext :: forall (p :: HyperType). (Ann a # p) -> Ann a # (HFunc p (Const (Ann a # p)) :*: p) Source #

HContext (App expr) Source # 
Instance details

Defined in Hyper.Syntax.App

Methods

hcontext :: forall (p :: HyperType). (App expr # p) -> App expr # (HFunc p (Const (App expr # p)) :*: p) Source #

HContext (FuncType typ) Source # 
Instance details

Defined in Hyper.Syntax.FuncType

Methods

hcontext :: forall (p :: HyperType). (FuncType typ # p) -> FuncType typ # (HFunc p (Const (FuncType typ # p)) :*: p) Source #

(HFunctor c1, HContext c1, HFunctor h1, HContext h1) => HContext (HCompose c1 h1) Source # 
Instance details

Defined in Hyper.Class.Context

Methods

hcontext :: forall (p :: HyperType). (HCompose c1 h1 # p) -> HCompose c1 h1 # (HFunc p (Const (HCompose c1 h1 # p)) :*: p) Source #

(Recursively HContext h, Recursively HFunctor h) => HContext (HFlip Ann h) Source # 
Instance details

Defined in Hyper.Class.Context

Methods

hcontext :: forall (p :: HyperType). (HFlip Ann h # p) -> HFlip Ann h # (HFunc p (Const (HFlip Ann h # p)) :*: p) Source #

HContext (Lam v expr) Source # 
Instance details

Defined in Hyper.Syntax.Lam

Methods

hcontext :: forall (p :: HyperType). (Lam v expr # p) -> Lam v expr # (HFunc p (Const (Lam v expr # p)) :*: p) Source #

HContext (Let v expr) Source # 
Instance details

Defined in Hyper.Syntax.Let

Methods

hcontext :: forall (p :: HyperType). (Let v expr # p) -> Let v expr # (HFunc p (Const (Let v expr # p)) :*: p) Source #

HContext (FromNom nomId term) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hcontext :: forall (p :: HyperType). (FromNom nomId term # p) -> FromNom nomId term # (HFunc p (Const (FromNom nomId term # p)) :*: p) Source #

(HFunctor varTypes, HContext varTypes, HNodesConstraint varTypes OrdQVar) => HContext (NominalInst nomId varTypes) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hcontext :: forall (p :: HyperType). (NominalInst nomId varTypes # p) -> NominalInst nomId varTypes # (HFunc p (Const (NominalInst nomId varTypes # p)) :*: p) Source #

HContext (ToNom nomId term) Source # 
Instance details

Defined in Hyper.Syntax.Nominal

Methods

hcontext :: forall (p :: HyperType). (ToNom nomId term # p) -> ToNom nomId term # (HFunc p (Const (ToNom nomId term # p)) :*: p) Source #

HContext (Var v expr) Source # 
Instance details

Defined in Hyper.Syntax.Var

Methods

hcontext :: forall (p :: HyperType). (Var v expr # p) -> Var v expr # (HFunc p (Const (Var v expr # p)) :*: p) Source #

HContext (RowExtend key val rest) Source # 
Instance details

Defined in Hyper.Syntax.Row

Methods

hcontext :: forall (p :: HyperType). (RowExtend key val rest # p) -> RowExtend key val rest # (HFunc p (Const (RowExtend key val rest # p)) :*: p) Source #

HContext (TypedLam var typ expr) Source # 
Instance details

Defined in Hyper.Syntax.TypedLam

Methods

hcontext :: forall (p :: HyperType). (TypedLam var typ expr # p) -> TypedLam var typ expr # (HFunc p (Const (TypedLam var typ expr # p)) :*: p) Source #

recursiveContexts :: (Recursively HContext h, Recursively HFunctor h, Recursively HContext p, Recursively HFunctor p) => (p # h) -> HCompose (Ann (HFunc Pure (Const (p # h)))) p # h Source #

Add in the node annotations a function to replace each node in the top-level node

annContexts :: (Recursively HContext h, Recursively HFunctor h) => (Ann p # h) -> Ann (HFunc (Ann p) (Const (Ann p # h)) :*: p) # h Source #

Add in the node annotations a function to replace each node in the top-level node

It is possible to define annContexts in terms of recursiveContexts but the conversion is quite unwieldy.