free-foil-0.0.2: Efficient Type-Safe Capture-Avoiding Substitution for Free (Scoped Monads)
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Free.Foil

Description

This module defines a variation of free scoped (relative) monads relying on the foil for the scope-safe efficient handling of the binders.

See description of the approach in «Free Foil: Generating Efficient and Scope-Safe Abstract Syntax».

Synopsis

Documentation

data ScopedAST (sig :: Type -> Type -> Type) (n :: S) where Source #

Scoped term under a (single) name binder.

Constructors

ScopedAST :: forall (n :: S) (l :: S) (sig :: Type -> Type -> Type). NameBinder n l -> AST sig l -> ScopedAST sig n 

Instances

Instances details
(forall (l :: S). NFData (AST sig l)) => NFData (ScopedAST sig n) Source # 
Instance details

Defined in Control.Monad.Free.Foil

Methods

rnf :: ScopedAST sig n -> () #

data AST (sig :: Type -> Type -> Type) (n :: S) where Source #

A term, generated by a signature Bifunctor sig, with (free) variables in scope n.

Constructors

Var :: forall (n :: S) (sig :: Type -> Type -> Type). Name n -> AST sig n

A (free) variable in scope n.

Node :: forall (sig :: Type -> Type -> Type) (n :: S). sig (ScopedAST sig n) (AST sig n) -> AST sig n

A non-variable syntactic construction specified by the signature Bifunctor sig.

Instances

Instances details
Bifunctor sig => RelMonad Name (AST sig) Source #

AST sig is a monad relative to Name.

Instance details

Defined in Control.Monad.Free.Foil

Methods

rreturn :: forall (a :: S). Name a -> AST sig a Source #

rbind :: forall (b :: S) (a :: S). Distinct b => Scope b -> AST sig a -> (Name a -> AST sig b) -> AST sig b Source #

Show (Expr n) Source #

Use ppExpr to show \(\lambda\)-terms.

Instance details

Defined in Control.Monad.Free.Foil.Example

Methods

showsPrec :: Int -> Expr n -> ShowS #

show :: Expr n -> String #

showList :: [Expr n] -> ShowS #

InjectName (AST sig) Source # 
Instance details

Defined in Control.Monad.Free.Foil

Methods

injectName :: forall (n :: S). Name n -> AST sig n Source #

Bifunctor sig => Sinkable (AST sig) Source # 
Instance details

Defined in Control.Monad.Free.Foil

Methods

sinkabilityProof :: forall (n :: S) (l :: S). (Name n -> Name l) -> AST sig n -> AST sig l Source #

Generic (AST sig n) Source # 
Instance details

Defined in Control.Monad.Free.Foil

Associated Types

type Rep (AST sig n) 
Instance details

Defined in Control.Monad.Free.Foil

type Rep (AST sig n) = D1 ('MetaData "AST" "Control.Monad.Free.Foil" "free-foil-0.0.2-5gpHStb7Jru4683iUcpcI7" 'False) (C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name n))) :+: C1 ('MetaCons "Node" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (sig (ScopedAST sig n) (AST sig n)))))

Methods

from :: AST sig n -> Rep (AST sig n) x #

to :: Rep (AST sig n) x -> AST sig n #

(forall scope term. (NFData scope, NFData term) => NFData (sig scope term)) => NFData (AST sig n) Source # 
Instance details

Defined in Control.Monad.Free.Foil

Methods

rnf :: AST sig n -> () #

type Rep (AST sig n) Source # 
Instance details

Defined in Control.Monad.Free.Foil

type Rep (AST sig n) = D1 ('MetaData "AST" "Control.Monad.Free.Foil" "free-foil-0.0.2-5gpHStb7Jru4683iUcpcI7" 'False) (C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name n))) :+: C1 ('MetaCons "Node" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (sig (ScopedAST sig n) (AST sig n)))))

substitute :: forall (sig :: Type -> Type -> Type) (o :: S) (i :: S). (Bifunctor sig, Distinct o) => Scope o -> Substitution (AST sig) i o -> AST sig i -> AST sig o Source #

Substitution for free (scoped monads).