glambda-1.0.2: A simply typed lambda calculus interpreter, written with GADTs

Copyright(C) 2015 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (rae@cs.brynmawr.edu)
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Language.Glambda.Type

Contents

Description

Defines types

Synopsis

Glambda types to be used in Haskell terms

data Ty Source #

Representation of a glambda type

Constructors

Arr Ty Ty infixr 1

A function type

IntTy 
BoolTy 

Instances

Eq Ty Source # 

Methods

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

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

Show Ty Source # 

Methods

showsPrec :: Int -> Ty -> ShowS #

show :: Ty -> String #

showList :: [Ty] -> ShowS #

Pretty Ty Source # 

Methods

pretty :: Ty -> Doc #

prettyList :: [Ty] -> Doc #

readTyCon :: String -> Maybe Ty Source #

Perhaps convert a string representation of a base type into a Ty

Glambda types to be used in Haskell types

data STy :: * -> * where Source #

Singleton for a glambda type

Constructors

SArr :: STy arg -> STy res -> STy (arg -> res) infixr 1 
SIntTy :: STy Int 
SBoolTy :: STy Bool 

Instances

Pretty (STy ty) Source # 

Methods

pretty :: STy ty -> Doc #

prettyList :: [STy ty] -> Doc #

data SCtx :: [*] -> * where Source #

Singleton for a typing context

Constructors

SNil :: SCtx '[] 
SCons :: STy h -> SCtx t -> SCtx (h ': t) infixr 5 

class ITy ty where Source #

An implicit STy, wrapped up in a class constraint

Minimal complete definition

sty

Methods

sty :: STy ty Source #

Instances

ITy Bool Source # 

Methods

sty :: STy Bool Source #

ITy Int Source # 

Methods

sty :: STy Int Source #

(ITy arg, ITy res) => ITy (arg -> res) Source # 

Methods

sty :: STy (arg -> res) Source #

emptyContext :: SCtx '[] Source #

The singleton for the empty context

refineTy :: Ty -> (forall ty. STy ty -> r) -> r Source #

Convert a Ty into an STy.

unrefineTy :: STy ty -> Ty Source #

Convert an STy into a Ty

eqSTy :: STy ty1 -> STy ty2 -> Maybe (ty1 :~: ty2) Source #

Compare two STys for equality.