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

Type.Check.HM.Infer

Description

Defines type-inference algorithm.

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 = ()              -- ^ define type for source code locations
  type Var  TestLang = Text            -- ^ define type for variables
  type Prim TestLang = NoPrim          -- ^ define type for primitive operators
  getPrimType _ _ = error "No primops"   -- ^ reports types for primitives

Also we define context for type inference that holds types for all known variables Often it defines types for all global variables or functions that are external.

context = Context $ Map.fromList [...]

Then we can use inference to derive type for given term with inferType or we can derive types for all sub-expressions of given term with inferTerm. See module in the test TM.Infer for examples of the usage.

termI,termK :: Term NoPrim () Text

-- I combinator
termI = lamE () "x" $ varE () "x"
-- K combinator
termK = lamE () "x" $ lamE () "y" $ varE () "x"

-- Let's infer types
typeI = inferType mempty termI
typeK = inferType mempty termK

There are functions to check that two types unify (unifyTypes) or that one type is subtype of another one (subtypeOf).

Synopsis

Context

data Context loc v Source #

Context holds map of proven signatures for free variables in the expression.

Constructors

Context 

Fields

Instances

Instances details
CanApply Context Source # 
Instance details

Defined in Type.Check.HM.Infer

Methods

apply :: Ord v => Subst loc v -> Context loc v -> Context loc v Source #

(Eq v, Eq loc) => Eq (Context loc v) Source # 
Instance details

Defined in Type.Check.HM.Infer

Methods

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

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

(Show v, Show loc) => Show (Context loc v) Source # 
Instance details

Defined in Type.Check.HM.Infer

Methods

showsPrec :: Int -> Context loc v -> ShowS #

show :: Context loc v -> String #

showList :: [Context loc v] -> ShowS #

Ord v => Semigroup (Context loc v) Source # 
Instance details

Defined in Type.Check.HM.Infer

Methods

(<>) :: Context loc v -> Context loc v -> Context loc v #

sconcat :: NonEmpty (Context loc v) -> Context loc v #

stimes :: Integral b => b -> Context loc v -> Context loc v #

Ord v => Monoid (Context loc v) Source # 
Instance details

Defined in Type.Check.HM.Infer

Methods

mempty :: Context loc v #

mappend :: Context loc v -> Context loc v -> Context loc v #

mconcat :: [Context loc v] -> Context loc v #

insertCtx :: Ord v => v -> Signature loc v -> Context loc v -> Context loc v Source #

Insert signature into context

lookupCtx :: Ord v => v -> Context loc v -> Maybe (Signature loc v) Source #

Lookup signature by name in the context of inferred terms.

insertConstructorCtx :: Ord v => v -> Signature loc v -> Context loc v -> Context loc v Source #

Insert signature into context

lookupConstructorCtx :: Ord v => v -> Context loc v -> Maybe (Signature loc v) Source #

Lookup signature by name in the context of inferred terms.

type ContextOf q = Context (Src q) (Var q) Source #

Type synonym for context.

Inference

inferType :: Lang q => ContextOf q -> TermOf q -> Either [ErrorOf q] (TypeOf q) Source #

Type-inference function. We provide a context of already proven type-signatures and term to infer the type.

inferTerm :: Lang q => ContextOf q -> TermOf q -> Either [ErrorOf q] (TyTermOf q) Source #

Infers types for all subexpressions of the given term. We provide a context of already proven type-signatures and term to infer the type.

inferTypeList :: Lang q => ContextOf q -> [Bind (Src q) (Var q) (TermOf q)] -> Either [ErrorOf q] [Bind (Src q) (Var q) (TypeOf q)] Source #

Infers types for bunch of terms. Terms can be recursive and not-sorted by depndencies. It returns only top-level types for all terms.

inferTermList :: Lang q => ContextOf q -> [Bind (Src q) (Var q) (TermOf q)] -> Either [ErrorOf q] [Bind (Src q) (Var q) (TyTermOf q)] Source #

Infers types for bunch of terms. Terms can be recursive and not-sorted by depndencies.

subtypeOf :: (IsVar v, Show loc, Eq loc) => Type loc v -> Type loc v -> Either (TypeError loc v) (Subst loc v) Source #

Checks if first argument one type is subtype of the second one.

unifyTypes :: (Show loc, IsVar v, Eq loc) => Type loc v -> Type loc v -> Either (TypeError loc v) (Subst loc v) Source #

Checks weather two types unify. If they do it returns substitution that unifies them.

Utils

closeSignature :: Ord var => [Type loc var] -> Signature loc var -> Type loc var Source #

Substitutes all type arguments with given types.

printInfer :: PrettyLang q => Either [ErrorOf q] (TypeOf q) -> IO () Source #

Pretty printer for result of type-inference