hindley-milner-type-check-0.1.1.0: Type inference for Hindley-Milner based languages
Safe HaskellNone
LanguageHaskell2010

Type.Check.HM.Lang

Contents

Description

Main class for the library that defines common types and primitives for the language.

Synopsis

Lang

class (IsVar (Var q), Show (Src q), Show (Prim q), Eq (Src q)) => Lang q where Source #

Main class to define inference API. For type inference we have to define instance of the Lang class:

data NoPrim
  deriving (Show)

data TestLang

instance Lang TestLang where
  type Src  TestLang = ()
  type Var  TestLang = Text
  type Prim TestLang = NoPrim
  getPrimType _ = error "No primops"

Associated Types

type Var q = r | r -> q Source #

Variables for our language. Notice that this type should be injective in relation to type of Lang. We need to have unique type of variables for each language definition.

type Src q Source #

Source code locations

type Prim q Source #

Primitives

Methods

getPrimType :: Src q -> Prim q -> TypeOf q Source #

Reports type for primitive.

type TypeOf q = Type (Src q) (Var q) Source #

Types of our language

type TermOf q = Term (Prim q) (Src q) (Var q) Source #

|Terms of our language

type TyTermOf q = TyTerm (Prim q) (Src q) (Var q) Source #

Typed terms of our language

type SubstOf q = Subst (Src q) (Var q) Source #

Type substitutions

type ErrorOf q = TypeError (Src q) (Var q) Source #

Type errors of our language

type PrettyLang q = (Lang q, PrettyVar (Var q), Pretty (Src q)) Source #