tal-0.1.0.0: An implementation of Typed Assembly Language (Morrisett, Walker, Crary, Glew)

Safe HaskellNone
LanguageHaskell2010

C

Documentation

data Ty Source #

Constructors

TyVar TyName 
TyInt 
All (Bind [TyName] [Ty]) 
TyProd [Ty] 
Exists (Bind TyName Ty) 

Instances

Show Ty Source # 

Methods

showsPrec :: Int -> Ty -> ShowS #

show :: Ty -> String #

showList :: [Ty] -> ShowS #

Rep Ty Source # 

Methods

rep :: R Ty #

Alpha Ty Source # 

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Ty -> Ty #

fv' :: Collection f => AlphaCtx -> Ty -> f AnyName #

lfreshen' :: LFresh m => AlphaCtx -> Ty -> (Ty -> Perm AnyName -> m b) -> m b #

freshen' :: Fresh m => AlphaCtx -> Ty -> m (Ty, Perm AnyName) #

aeq' :: AlphaCtx -> Ty -> Ty -> Bool #

acompare' :: AlphaCtx -> Ty -> Ty -> Ordering #

close :: Alpha b => AlphaCtx -> b -> Ty -> Ty #

open :: Alpha b => AlphaCtx -> b -> Ty -> Ty #

isPat :: Ty -> Maybe [AnyName] #

isTerm :: Ty -> Bool #

isEmbed :: Ty -> Bool #

nthpatrec :: Ty -> NthCont #

findpatrec :: Ty -> AnyName -> FindResult #

Display Ty Source # 

Methods

display :: Ty -> DM Doc Source #

(Sat (ctx0 TyName), Sat (ctx0 (Bind [TyName] [Ty])), Sat (ctx0 [Ty]), Sat (ctx0 (Bind TyName Ty))) => Rep1 ctx0 Ty Source # 

Methods

rep1 :: R1 ctx0 Ty #

Subst Val Ty Source # 

Methods

isvar :: Ty -> Maybe (SubstName Ty Val) #

isCoerceVar :: Ty -> Maybe (SubstCoerce Ty Val) #

subst :: Name Val -> Val -> Ty -> Ty #

substs :: [(Name Val, Val)] -> Ty -> Ty #

substPat :: AlphaCtx -> Val -> Ty -> Ty #

substPats :: Proxy * Val -> AlphaCtx -> [Dyn] -> Ty -> Ty #

Subst Ty Prim Source # 
Subst Ty Tm Source # 

Methods

isvar :: Tm -> Maybe (SubstName Tm Ty) #

isCoerceVar :: Tm -> Maybe (SubstCoerce Tm Ty) #

subst :: Name Ty -> Ty -> Tm -> Tm #

substs :: [(Name Ty, Ty)] -> Tm -> Tm #

substPat :: AlphaCtx -> Ty -> Tm -> Tm #

substPats :: Proxy * Ty -> AlphaCtx -> [Dyn] -> Tm -> Tm #

Subst Ty Decl Source # 
Subst Ty AnnVal Source # 
Subst Ty Val Source # 

Methods

isvar :: Val -> Maybe (SubstName Val Ty) #

isCoerceVar :: Val -> Maybe (SubstCoerce Val Ty) #

subst :: Name Ty -> Ty -> Val -> Val #

substs :: [(Name Ty, Ty)] -> Val -> Val #

substPat :: AlphaCtx -> Ty -> Val -> Val #

substPats :: Proxy * Ty -> AlphaCtx -> [Dyn] -> Val -> Val #

Subst Ty Ty Source # 

Methods

isvar :: Ty -> Maybe (SubstName Ty Ty) #

isCoerceVar :: Ty -> Maybe (SubstCoerce Ty Ty) #

subst :: Name Ty -> Ty -> Ty -> Ty #

substs :: [(Name Ty, Ty)] -> Ty -> Ty #

substPat :: AlphaCtx -> Ty -> Ty -> Ty #

substPats :: Proxy * Ty -> AlphaCtx -> [Dyn] -> Ty -> Ty #

Display (ValName, Embed Ty) Source # 

Methods

display :: (ValName, Embed Ty) -> DM Doc Source #

data Val Source #

Instances

Show Val Source # 

Methods

showsPrec :: Int -> Val -> ShowS #

show :: Val -> String #

showList :: [Val] -> ShowS #

Rep Val Source # 

Methods

rep :: R Val #

Alpha Val Source # 

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Val -> Val #

fv' :: Collection f => AlphaCtx -> Val -> f AnyName #

lfreshen' :: LFresh m => AlphaCtx -> Val -> (Val -> Perm AnyName -> m b) -> m b #

freshen' :: Fresh m => AlphaCtx -> Val -> m (Val, Perm AnyName) #

aeq' :: AlphaCtx -> Val -> Val -> Bool #

acompare' :: AlphaCtx -> Val -> Val -> Ordering #

close :: Alpha b => AlphaCtx -> b -> Val -> Val #

open :: Alpha b => AlphaCtx -> b -> Val -> Val #

isPat :: Val -> Maybe [AnyName] #

isTerm :: Val -> Bool #

isEmbed :: Val -> Bool #

nthpatrec :: Val -> NthCont #

findpatrec :: Val -> AnyName -> FindResult #

Display Val Source # 

Methods

display :: Val -> DM Doc Source #

(Sat (ctx0 Int), Sat (ctx0 ValName), Sat (ctx0 (Bind (ValName, [TyName]) (Bind [(ValName, Embed Ty)] Tm))), Sat (ctx0 [AnnVal]), Sat (ctx0 AnnVal), Sat (ctx0 Ty)) => Rep1 ctx0 Val Source # 

Methods

rep1 :: R1 ctx0 Val #

Subst Val Prim Source # 
Subst Val Tm Source # 

Methods

isvar :: Tm -> Maybe (SubstName Tm Val) #

isCoerceVar :: Tm -> Maybe (SubstCoerce Tm Val) #

subst :: Name Val -> Val -> Tm -> Tm #

substs :: [(Name Val, Val)] -> Tm -> Tm #

substPat :: AlphaCtx -> Val -> Tm -> Tm #

substPats :: Proxy * Val -> AlphaCtx -> [Dyn] -> Tm -> Tm #

Subst Val Decl Source # 
Subst Val AnnVal Source # 
Subst Val Val Source # 
Subst Val Ty Source # 

Methods

isvar :: Ty -> Maybe (SubstName Ty Val) #

isCoerceVar :: Ty -> Maybe (SubstCoerce Ty Val) #

subst :: Name Val -> Val -> Ty -> Ty #

substs :: [(Name Val, Val)] -> Ty -> Ty #

substPat :: AlphaCtx -> Val -> Ty -> Ty #

substPats :: Proxy * Val -> AlphaCtx -> [Dyn] -> Ty -> Ty #

Subst Ty Val Source # 

Methods

isvar :: Val -> Maybe (SubstName Val Ty) #

isCoerceVar :: Val -> Maybe (SubstCoerce Val Ty) #

subst :: Name Ty -> Ty -> Val -> Val #

substs :: [(Name Ty, Ty)] -> Val -> Val #

substPat :: AlphaCtx -> Ty -> Val -> Val #

substPats :: Proxy * Ty -> AlphaCtx -> [Dyn] -> Val -> Val #

Display (ValName, Embed Ty) Source # 

Methods

display :: (ValName, Embed Ty) -> DM Doc Source #

data AnnVal Source #

Constructors

Ann Val Ty 

Instances

Show AnnVal Source # 
Rep AnnVal Source # 

Methods

rep :: R AnnVal #

Alpha AnnVal Source # 
Display AnnVal Source # 

Methods

display :: AnnVal -> DM Doc Source #

(Sat (ctx0 Val), Sat (ctx0 Ty)) => Rep1 ctx0 AnnVal Source # 

Methods

rep1 :: R1 ctx0 AnnVal #

Subst Val AnnVal Source # 
Subst Ty AnnVal Source # 

data Decl Source #

Instances

Show Decl Source # 

Methods

showsPrec :: Int -> Decl -> ShowS #

show :: Decl -> String #

showList :: [Decl] -> ShowS #

Rep Decl Source # 

Methods

rep :: R Decl #

Alpha Decl Source # 

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Decl -> Decl #

fv' :: Collection f => AlphaCtx -> Decl -> f AnyName #

lfreshen' :: LFresh m => AlphaCtx -> Decl -> (Decl -> Perm AnyName -> m b) -> m b #

freshen' :: Fresh m => AlphaCtx -> Decl -> m (Decl, Perm AnyName) #

aeq' :: AlphaCtx -> Decl -> Decl -> Bool #

acompare' :: AlphaCtx -> Decl -> Decl -> Ordering #

close :: Alpha b => AlphaCtx -> b -> Decl -> Decl #

open :: Alpha b => AlphaCtx -> b -> Decl -> Decl #

isPat :: Decl -> Maybe [AnyName] #

isTerm :: Decl -> Bool #

isEmbed :: Decl -> Bool #

nthpatrec :: Decl -> NthCont #

findpatrec :: Decl -> AnyName -> FindResult #

Display Decl Source # 

Methods

display :: Decl -> DM Doc Source #

(Sat (ctx0 ValName), Sat (ctx0 (Embed AnnVal)), Sat (ctx0 Int), Sat (ctx0 (Embed (AnnVal, Prim, AnnVal))), Sat (ctx0 TyName)) => Rep1 ctx0 Decl Source # 

Methods

rep1 :: R1 ctx0 Decl #

Subst Val Decl Source # 
Subst Ty Decl Source # 

data Tm Source #

Instances

Show Tm Source # 

Methods

showsPrec :: Int -> Tm -> ShowS #

show :: Tm -> String #

showList :: [Tm] -> ShowS #

Rep Tm Source # 

Methods

rep :: R Tm #

Alpha Tm Source # 

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Tm -> Tm #

fv' :: Collection f => AlphaCtx -> Tm -> f AnyName #

lfreshen' :: LFresh m => AlphaCtx -> Tm -> (Tm -> Perm AnyName -> m b) -> m b #

freshen' :: Fresh m => AlphaCtx -> Tm -> m (Tm, Perm AnyName) #

aeq' :: AlphaCtx -> Tm -> Tm -> Bool #

acompare' :: AlphaCtx -> Tm -> Tm -> Ordering #

close :: Alpha b => AlphaCtx -> b -> Tm -> Tm #

open :: Alpha b => AlphaCtx -> b -> Tm -> Tm #

isPat :: Tm -> Maybe [AnyName] #

isTerm :: Tm -> Bool #

isEmbed :: Tm -> Bool #

nthpatrec :: Tm -> NthCont #

findpatrec :: Tm -> AnyName -> FindResult #

Display Tm Source # 

Methods

display :: Tm -> DM Doc Source #

(Sat (ctx0 (Bind Decl Tm)), Sat (ctx0 AnnVal), Sat (ctx0 [AnnVal]), Sat (ctx0 Tm), Sat (ctx0 Ty)) => Rep1 ctx0 Tm Source # 

Methods

rep1 :: R1 ctx0 Tm #

Subst Val Tm Source # 

Methods

isvar :: Tm -> Maybe (SubstName Tm Val) #

isCoerceVar :: Tm -> Maybe (SubstCoerce Tm Val) #

subst :: Name Val -> Val -> Tm -> Tm #

substs :: [(Name Val, Val)] -> Tm -> Tm #

substPat :: AlphaCtx -> Val -> Tm -> Tm #

substPats :: Proxy * Val -> AlphaCtx -> [Dyn] -> Tm -> Tm #

Subst Ty Tm Source # 

Methods

isvar :: Tm -> Maybe (SubstName Tm Ty) #

isCoerceVar :: Tm -> Maybe (SubstCoerce Tm Ty) #

subst :: Name Ty -> Ty -> Tm -> Tm #

substs :: [(Name Ty, Ty)] -> Tm -> Tm #

substPat :: AlphaCtx -> Ty -> Tm -> Tm #

substPats :: Proxy * Ty -> AlphaCtx -> [Dyn] -> Tm -> Tm #

Display (Tm, Heap) Source # 

Methods

display :: (Tm, Heap) -> DM Doc Source #

newtype Heap Source #

Constructors

Heap (Map ValName AnnVal) 

Instances

rTm1 :: forall ctx. ctx (Bind Decl Tm) -> (ctx AnnVal, ctx [AnnVal]) -> (ctx AnnVal, ctx Tm, ctx Tm) -> (ctx Ty, ctx AnnVal) -> R1 ctx Tm Source #

rDecl1 :: forall ctx. (ctx ValName, ctx (Embed AnnVal)) -> (ctx Int, ctx ValName, ctx (Embed AnnVal)) -> (ctx ValName, ctx (Embed (AnnVal, Prim, AnnVal))) -> (ctx TyName, ctx ValName, ctx (Embed AnnVal)) -> R1 ctx Decl Source #

rAnnVal1 :: forall ctx. (ctx Val, ctx Ty) -> R1 ctx AnnVal Source #

rVal1 :: forall ctx. ctx Int -> ctx ValName -> ctx (Bind (ValName, [TyName]) (Bind [(ValName, Embed Ty)] Tm)) -> ctx [AnnVal] -> (ctx AnnVal, ctx Ty) -> (ctx Ty, ctx AnnVal) -> R1 ctx Val Source #

rTy1 :: forall ctx. ctx TyName -> () -> ctx (Bind [TyName] [Ty]) -> ctx [Ty] -> ctx (Bind TyName Ty) -> R1 ctx Ty Source #

type Delta = [TyName] Source #

type Gamma = [(ValName, Ty)] Source #

data Ctx Source #

Constructors

Ctx 

Fields

extendTms :: [ValName] -> [Ty] -> Ctx -> Ctx Source #

tcty :: Ctx -> Ty -> M () Source #

typecheck :: Ctx -> Tm -> M () Source #

mkSubst :: Decl -> M (Tm -> Tm) Source #

step :: Tm -> M Tm Source #