ltext-0.1.3: Parameterized file evaluator

Safe HaskellNone
LanguageHaskell2010

LText.Type

Contents

Synopsis

Type Grammar

data Type Source #

We're working in an implicitly quantified prenex-polymorphic type system, so trivial type expressions are also type schemes.

Constructors

Text 
TVar String 
TArrow Type Type 
Instances
Eq Type Source # 
Instance details

Defined in LText.Type

Methods

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

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

Show Type Source # 
Instance details

Defined in LText.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

IsType Type Source # 
Instance details

Defined in LText.Type

Kit Effects

data TypeError Source #

Instances
Eq TypeError Source # 
Instance details

Defined in LText.Type

Show TypeError Source # 
Instance details

Defined in LText.Type

Generic TypeError Source # 
Instance details

Defined in LText.Type

Associated Types

type Rep TypeError :: Type -> Type #

Exception TypeError Source # 
Instance details

Defined in LText.Type

type Rep TypeError Source # 
Instance details

Defined in LText.Type

data TypeEnv Source #

Constructors

TypeEnv 
Instances
Eq TypeEnv Source # 
Instance details

Defined in LText.Type

Methods

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

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

Show TypeEnv Source # 
Instance details

Defined in LText.Type

TypeChecking

newtype Subst Source #

Constructors

Subst 
Instances
Eq Subst Source # 
Instance details

Defined in LText.Type

Methods

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

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

Show Subst Source # 
Instance details

Defined in LText.Type

Methods

showsPrec :: Int -> Subst -> ShowS #

show :: Subst -> String #

showList :: [Subst] -> ShowS #

Semigroup Subst Source # 
Instance details

Defined in LText.Type

Methods

(<>) :: Subst -> Subst -> Subst #

sconcat :: NonEmpty Subst -> Subst #

stimes :: Integral b => b -> Subst -> Subst #

Monoid Subst Source # 
Instance details

Defined in LText.Type

Methods

mempty :: Subst #

mappend :: Subst -> Subst -> Subst #

mconcat :: [Subst] -> Subst #

class IsType t where Source #

Methods

freeTVars :: t -> HashSet String Source #

applySubst :: Subst -> t -> t Source #

Instances
IsType Context Source # 
Instance details

Defined in LText.Type

IsType Scheme Source # 
Instance details

Defined in LText.Type

IsType Type Source # 
Instance details

Defined in LText.Type

IsType a => IsType [a] Source # 
Instance details

Defined in LText.Type

Methods

freeTVars :: [a] -> HashSet String Source #

applySubst :: Subst -> [a] -> [a] Source #

data Scheme Source #

Constructors

Scheme 
Instances
Eq Scheme Source # 
Instance details

Defined in LText.Type

Methods

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

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

Show Scheme Source # 
Instance details

Defined in LText.Type

IsType Scheme Source # 
Instance details

Defined in LText.Type

varBind :: MonadTypecheck m => String -> Type -> m Subst Source #

Substitute n for t, given there's no collision

data Context Source #

Constructors

Context 
Instances
Eq Context Source # 
Instance details

Defined in LText.Type

Methods

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

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

Show Context Source # 
Instance details

Defined in LText.Type

IsType Context Source # 
Instance details

Defined in LText.Type

quantify :: MonadTypecheck m => Type -> m Scheme Source #

Where we don't want to include variables bound by our context

unQuantify :: MonadTypecheck m => Scheme -> m Type Source #

Replaces bound variables with fresh ones

Actual Typechecking

data ExprType Source #

Constructors

TopLevel 
DocLevel