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

Safe HaskellNone
LanguageHaskell2010

TAL

Synopsis

Documentation

data Ty Source #

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] Gamma)), Sat (ctx0 [(Ty, Flag)]), Sat (ctx0 (Bind TyName Ty))) => Rep1 ctx0 Ty Source # 

Methods

rep1 :: R1 ctx0 Ty #

Subst Ty InstrSeq Source # 
Subst Ty Instruction Source # 
Subst Ty HeapVal Source # 
Subst Ty SmallVal Source # 
Subst Ty WordVal Source # 
Subst Ty Label Source # 
Subst Ty Register Source # 
Subst Ty Flag Source # 
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 #

Subst Ty a => Subst Ty (Pack a) Source # 

Methods

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

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

subst :: Name Ty -> Ty -> Pack a -> Pack a #

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

substPat :: AlphaCtx -> Ty -> Pack a -> Pack a #

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

Subst Ty a => Subst Ty (TyApp a) Source # 

Methods

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

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

subst :: Name Ty -> Ty -> TyApp a -> TyApp a #

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

substPat :: AlphaCtx -> Ty -> TyApp a -> TyApp a #

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

(Rep a, Subst Ty b) => Subst Ty (Map a b) Source # 

Methods

isvar :: Map a b -> Maybe (SubstName (Map a b) Ty) #

isCoerceVar :: Map a b -> Maybe (SubstCoerce (Map a b) Ty) #

subst :: Name Ty -> Ty -> Map a b -> Map a b #

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

substPat :: AlphaCtx -> Ty -> Map a b -> Map a b #

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

Display (Ty, Flag) Source # 

Methods

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

data Flag Source #

Constructors

Un 
Init 

Instances

Eq Flag Source # 

Methods

(==) :: Flag -> Flag -> Bool #

(/=) :: Flag -> Flag -> Bool #

Ord Flag Source # 

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

(>=) :: Flag -> Flag -> Bool #

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Show Flag Source # 

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Rep Flag Source # 

Methods

rep :: R Flag #

Alpha Flag Source # 

Methods

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

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

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

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

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

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

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

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

isPat :: Flag -> Maybe [AnyName] #

isTerm :: Flag -> Bool #

isEmbed :: Flag -> Bool #

nthpatrec :: Flag -> NthCont #

findpatrec :: Flag -> AnyName -> FindResult #

Rep1 ctx0 Flag Source # 

Methods

rep1 :: R1 ctx0 Flag #

Subst Ty Flag Source # 
Display (Ty, Flag) Source # 

Methods

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

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

newtype Register Source #

Constructors

Register String 

Instances

Enum Register Source # 
Eq Register Source # 
Ord Register Source # 
Show Register Source # 
Rep Register Source # 

Methods

rep :: R Register #

Alpha Register Source # 
Sat (ctx0 String) => Rep1 ctx0 Register Source # 

Methods

rep1 :: R1 ctx0 Register #

Subst Ty Register Source # 
Display a => Display [(Register, a)] Source # 

Methods

display :: [(Register, a)] -> DM Doc Source #

Alpha b => Alpha (Map Register b) Source # 
Display a => Display (Map Register a) Source # 

Methods

display :: Map Register a -> DM Doc Source #

Display (Heap, RegisterFile, InstrSeq) Source # 

newtype Label Source #

Constructors

Label (Name Heap) 

Instances

Eq Label Source # 

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

Ord Label Source # 

Methods

compare :: Label -> Label -> Ordering #

(<) :: Label -> Label -> Bool #

(<=) :: Label -> Label -> Bool #

(>) :: Label -> Label -> Bool #

(>=) :: Label -> Label -> Bool #

max :: Label -> Label -> Label #

min :: Label -> Label -> Label #

Show Label Source # 

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Rep Label Source # 

Methods

rep :: R Label #

Alpha Label Source # 
Display Label Source # 

Methods

display :: Label -> DM Doc Source #

Sat (ctx0 (Name Heap)) => Rep1 ctx0 Label Source # 

Methods

rep1 :: R1 ctx0 Label #

Subst Ty Label Source # 
Display a => Display (Map Label a) Source # 

Methods

display :: Map Label a -> DM Doc Source #

Display (Heap, RegisterFile, InstrSeq) Source # 

data TyApp a Source #

Constructors

TyApp a Ty 

Instances

(Rep a0, Sat (ctx0 a0), Sat (ctx0 Ty)) => Rep1 ctx0 (TyApp a0) Source # 

Methods

rep1 :: R1 ctx0 (TyApp a0) #

Subst Ty a => Subst Ty (TyApp a) Source # 

Methods

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

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

subst :: Name Ty -> Ty -> TyApp a -> TyApp a #

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

substPat :: AlphaCtx -> Ty -> TyApp a -> TyApp a #

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

Show a => Show (TyApp a) Source # 

Methods

showsPrec :: Int -> TyApp a -> ShowS #

show :: TyApp a -> String #

showList :: [TyApp a] -> ShowS #

Rep a0 => Rep (TyApp a0) Source # 

Methods

rep :: R (TyApp a0) #

Alpha a => Alpha (TyApp a) Source # 

Methods

swaps' :: AlphaCtx -> Perm AnyName -> TyApp a -> TyApp a #

fv' :: Collection f => AlphaCtx -> TyApp a -> f AnyName #

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

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

aeq' :: AlphaCtx -> TyApp a -> TyApp a -> Bool #

acompare' :: AlphaCtx -> TyApp a -> TyApp a -> Ordering #

close :: Alpha b => AlphaCtx -> b -> TyApp a -> TyApp a #

open :: Alpha b => AlphaCtx -> b -> TyApp a -> TyApp a #

isPat :: TyApp a -> Maybe [AnyName] #

isTerm :: TyApp a -> Bool #

isEmbed :: TyApp a -> Bool #

nthpatrec :: TyApp a -> NthCont #

findpatrec :: TyApp a -> AnyName -> FindResult #

Display a => Display (TyApp a) Source # 

Methods

display :: TyApp a -> DM Doc Source #

data Pack a Source #

Constructors

Pack Ty a Ty 

Instances

(Rep a0, Sat (ctx0 Ty), Sat (ctx0 a0)) => Rep1 ctx0 (Pack a0) Source # 

Methods

rep1 :: R1 ctx0 (Pack a0) #

Subst Ty a => Subst Ty (Pack a) Source # 

Methods

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

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

subst :: Name Ty -> Ty -> Pack a -> Pack a #

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

substPat :: AlphaCtx -> Ty -> Pack a -> Pack a #

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

Show a => Show (Pack a) Source # 

Methods

showsPrec :: Int -> Pack a -> ShowS #

show :: Pack a -> String #

showList :: [Pack a] -> ShowS #

Rep a0 => Rep (Pack a0) Source # 

Methods

rep :: R (Pack a0) #

Alpha a => Alpha (Pack a) Source # 

Methods

swaps' :: AlphaCtx -> Perm AnyName -> Pack a -> Pack a #

fv' :: Collection f => AlphaCtx -> Pack a -> f AnyName #

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

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

aeq' :: AlphaCtx -> Pack a -> Pack a -> Bool #

acompare' :: AlphaCtx -> Pack a -> Pack a -> Ordering #

close :: Alpha b => AlphaCtx -> b -> Pack a -> Pack a #

open :: Alpha b => AlphaCtx -> b -> Pack a -> Pack a #

isPat :: Pack a -> Maybe [AnyName] #

isTerm :: Pack a -> Bool #

isEmbed :: Pack a -> Bool #

nthpatrec :: Pack a -> NthCont #

findpatrec :: Pack a -> AnyName -> FindResult #

Display a => Display (Pack a) Source # 

Methods

display :: Pack a -> DM Doc Source #

data WordVal Source #

Instances

Show WordVal Source # 
Rep WordVal Source # 

Methods

rep :: R WordVal #

Alpha WordVal Source # 
Display WordVal Source # 

Methods

display :: WordVal -> DM Doc Source #

(Sat (ctx0 Label), Sat (ctx0 Int), Sat (ctx0 Ty), Sat (ctx0 (TyApp WordVal)), Sat (ctx0 (Pack WordVal))) => Rep1 ctx0 WordVal Source # 

Methods

rep1 :: R1 ctx0 WordVal #

Subst Ty WordVal Source # 
Display (Heap, RegisterFile, InstrSeq) Source # 

data SmallVal Source #

Instances

Show SmallVal Source # 
Rep SmallVal Source # 

Methods

rep :: R SmallVal #

Alpha SmallVal Source # 
Display SmallVal Source # 

Methods

display :: SmallVal -> DM Doc Source #

(Sat (ctx0 Register), Sat (ctx0 WordVal), Sat (ctx0 (TyApp SmallVal)), Sat (ctx0 (Pack SmallVal))) => Rep1 ctx0 SmallVal Source # 

Methods

rep1 :: R1 ctx0 SmallVal #

Subst Ty SmallVal Source # 

data HeapVal Source #

Constructors

Tuple [WordVal] 
Code [TyName] Gamma InstrSeq 

Instances

Show HeapVal Source # 
Rep HeapVal Source # 

Methods

rep :: R HeapVal #

Alpha HeapVal Source # 
Display HeapVal Source # 

Methods

display :: HeapVal -> DM Doc Source #

(Sat (ctx0 [WordVal]), Sat (ctx0 [TyName]), Sat (ctx0 Gamma), Sat (ctx0 InstrSeq)) => Rep1 ctx0 HeapVal Source # 

Methods

rep1 :: R1 ctx0 HeapVal #

Subst Ty HeapVal Source # 
Display (Heap, RegisterFile, InstrSeq) Source # 

data Instruction Source #

Instances

Show Instruction Source # 
Rep Instruction Source # 

Methods

rep :: R Instruction #

Alpha Instruction Source # 
Display Instruction Source # 
(Sat (ctx0 Register), Sat (ctx0 SmallVal), Sat (ctx0 Int), Sat (ctx0 [Ty]), Sat (ctx0 TyName)) => Rep1 ctx0 Instruction Source # 

Methods

rep1 :: R1 ctx0 Instruction #

Subst Ty Instruction Source # 

data InstrSeq Source #

Instances

Show InstrSeq Source # 
Rep InstrSeq Source # 

Methods

rep :: R InstrSeq #

Alpha InstrSeq Source # 
Display InstrSeq Source # 

Methods

display :: InstrSeq -> DM Doc Source #

(Sat (ctx0 Instruction), Sat (ctx0 InstrSeq), Sat (ctx0 SmallVal), Sat (ctx0 Ty)) => Rep1 ctx0 InstrSeq Source # 

Methods

rep1 :: R1 ctx0 InstrSeq #

Subst Ty InstrSeq Source # 
Display (Heap, RegisterFile, InstrSeq) Source # 

rInstrSeq1 :: forall ctx. (ctx Instruction, ctx InstrSeq) -> ctx SmallVal -> ctx Ty -> R1 ctx InstrSeq Source #

rInstruction1 :: forall ctx. (ctx Register, ctx Register, ctx SmallVal) -> (ctx Register, ctx SmallVal) -> (ctx Register, ctx Register, ctx Int) -> (ctx Register, ctx [Ty]) -> (ctx Register, ctx SmallVal) -> (ctx Register, ctx Register, ctx SmallVal) -> (ctx Register, ctx Int, ctx Register) -> (ctx Register, ctx Register, ctx SmallVal) -> (ctx TyName, ctx Register, ctx SmallVal) -> R1 ctx Instruction Source #

rHeapVal1 :: forall ctx. ctx [WordVal] -> (ctx [TyName], ctx Gamma, ctx InstrSeq) -> R1 ctx HeapVal Source #

rSmallVal1 :: forall ctx. ctx Register -> ctx WordVal -> ctx (TyApp SmallVal) -> ctx (Pack SmallVal) -> R1 ctx SmallVal Source #

rWordVal1 :: forall ctx. ctx Label -> ctx Int -> ctx Ty -> ctx (TyApp WordVal) -> ctx (Pack WordVal) -> R1 ctx WordVal Source #

rPack1 :: forall ctx a. Rep a => (ctx Ty, ctx a, ctx Ty) -> R1 ctx (Pack a) Source #

rPack :: forall a. Rep a => R (Pack a) Source #

rTyApp1 :: forall ctx a. Rep a => (ctx a, ctx Ty) -> R1 ctx (TyApp a) Source #

rTyApp :: forall a. Rep a => R (TyApp a) Source #

rLabel1 :: forall ctx. ctx (Name Heap) -> R1 ctx Label Source #

rRegister1 :: forall ctx. ctx String -> R1 ctx Register Source #

rFlag1 :: forall ctx. () -> () -> R1 ctx Flag Source #

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

type Delta = [TyName] Source #

data Ctx Source #

Constructors

Ctx 

Fields

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

tcPsi :: Ctx -> Psi -> M () Source #

tcGamma :: Ctx -> Gamma -> M () Source #

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

subGamma :: Ctx -> Gamma -> Gamma -> M () Source #

typeCheckHeap :: Heap -> Psi -> M () Source #

  • H : Psi

tcApp :: (Ctx -> a -> M Ty) -> Ctx -> TyApp a -> M Ty Source #

tcPack :: Display a => (Ctx -> a -> M Ty) -> Ctx -> Pack a -> M Ty Source #

dispArith :: (Display t, Show a1, Show a) => String -> a -> a1 -> t -> DM Doc Source #