infernu-0.0.0.1: Type inference and checker for JavaScript (experimental)

Safe HaskellNone
LanguageHaskell2010

Infernu.InferState

Synopsis

Documentation

type Infer a = StateT InferState (EitherT TypeError Identity) a Source

Inference monad. Used as a stateful context for generating fresh type variable names.

areEquivalentNamedTypes :: (Type, TypeScheme) -> (Type, TypeScheme) -> Bool Source

Compares schemes up to alpha equivalence including named type constructors equivalence (TCons TName...).

>>> let mkNamedType tid ts = Fix $ TCons (TName (TypeId tid)) ts
>>> areEquivalentNamedTypes (mkNamedType 0 [], schemeEmpty (Fix $ TBody TNumber)) (mkNamedType 1 [], schemeEmpty (Fix $ TBody TString))
False
>>> areEquivalentNamedTypes (mkNamedType 0 [], schemeEmpty (mkNamedType 0 [])) (mkNamedType 1 [], schemeEmpty (mkNamedType 1 []))
True
>>> :{
    areEquivalentNamedTypes (mkNamedType 0 [], schemeEmpty (Fix $ TFunc [Fix $ TBody TNumber] (mkNamedType 0 [])))
                            (mkNamedType 1 [], schemeEmpty (Fix $ TFunc [Fix $ TBody TNumber] (mkNamedType 1 [])))
:}
True
>>> :{
    areEquivalentNamedTypes (mkNamedType 0 [Fix $ TBody $ TVar 10], TScheme [10] (qualEmpty $ Fix $ TFunc [Fix $ TBody $ TVar 10] (mkNamedType 0 [Fix $ TBody $ TVar 10])))
                            (mkNamedType 1 [Fix $ TBody $ TVar 11], TScheme [11] (qualEmpty $ Fix $ TFunc [Fix $ TBody $ TVar 11] (mkNamedType 1 [Fix $ TBody $ TVar 11])))
:}
True

replaceFixQual :: (Functor f, Eq (f (Fix f))) => f (Fix f) -> f (Fix f) -> TQual (Fix f) -> TQual (Fix f) Source

Returns a TQual with the src type replaced everywhere with the dest type.

isRecParamOnly :: (Num t, Enum t) => TVarName -> Maybe (TypeId, t) -> Type -> Maybe [(TypeId, t)] Source

dropAt :: Integral a => a -> [b] -> [b] Source

unrollName :: Source -> TypeId -> [Type] -> Infer QualType Source

Unrolls (expands) a TName recursive type by plugging in the holes from the given list of types. Similar to instantiation, but uses a pre-defined set of type instances instead of using fresh type variables.

applySubstInfer :: TSubst -> Infer () Source

Applies a subsitution onto the state (basically on the variable -> scheme map).

>>> :{
runInfer $ do
    let t = TScheme [0] (TQual [] (Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 1))))
    let tenv = Map.empty
    tenv' <- addVarScheme tenv "x" t
    applySubstInfer $ Map.singleton 0 (Fix $ TBody TString)
    varSchemes <$> get
:}
Right (fromList [(VarId 3,TScheme {schemeVars = [], schemeType = TQual {qualPred = [], qualType = Fix (TFunc [Fix (TBody TString)] Fix (TBody (TVar 1)))}})])

instantiateScheme :: Bool -> TypeScheme -> Infer QualType Source

Instantiate a type scheme by giving fresh names to all quantified type variables.

For example:

>>> runInferWith (emptyInferState { nameSource = NameSource 2 }) . instantiate $ TScheme [0] (TQual { qualPred = [], qualType = Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 1)) })
Right (TQual {qualPred = [], qualType = Fix (TFunc [Fix (TBody (TVar 3))] Fix (TBody (TVar 1)))})

In the above example, type variable 0 has been replaced with a fresh one (3), while the unqualified free type variable 1 has been left as-is.

>>> :{
runInfer $ do
    let t = TScheme [0] (TQual [] (Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 1))))
    let tenv = Map.empty
    tenv' <- addVarScheme tenv "x" t
    instantiateVar emptySource "x" tenv'
:}
Right (TQual {qualPred = [], qualType = Fix (TFunc [Fix (TBody (TVar 4))] Fix (TBody (TVar 1)))})

unsafeGeneralize :: TypeEnv -> QualType -> Infer TypeScheme Source

Generalizes a type to a type scheme, i.e. wraps it in a "forall" that quantifies over all type variables that are free in the given type, but are not free in the type environment.

Example:

>>> runInfer $ generalize (ELit "bla" LitUndefined) Map.empty $ qualEmpty $ Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 1))
Right (TScheme {schemeVars = [0,1], schemeType = TQual {qualPred = [], qualType = Fix (TFunc [Fix (TBody (TVar 0))] Fix (TBody (TVar 1)))}})
>>> :{
runInfer $ do
    let t = TScheme [1] (TQual [] (Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 1))))
    tenv <- addVarScheme Map.empty "x" t
    generalize (ELit "bla" LitUndefined) tenv (qualEmpty $ Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 2)))
:}
Right (TScheme {schemeVars = [2], schemeType = TQual {qualPred = [], qualType = Fix (TFunc [Fix (TBody (TVar 0))] Fix (TBody (TVar 2)))}})

In this example the steps were:

  1. Environment: { x :: forall 0. 0 -> 1 }
  2. generalize (1 -> 2)
  3. result: forall 2. 1 -> 2
>>> let expr = ELit "foo" LitUndefined
>>> runInfer $ generalize expr Map.empty (qualEmpty $ Fix $ TFunc [Fix $ TBody (TVar 0)] (Fix $ TBody (TVar 0)))
Right (TScheme {schemeVars = [0], schemeType = TQual {qualPred = [], qualType = Fix (TFunc [Fix (TBody (TVar 0))] Fix (TBody (TVar 0)))}})
>>> runInfer $ generalize expr Map.empty (TQual [TPredIsIn (ClassName "Bla") (Fix $ TBody (TVar 1))] (Fix $ TBody (TVar 0)))
Right (TScheme {schemeVars = [0,1], schemeType = TQual {qualPred = [TPredIsIn {predClass = ClassName "Bla", predType = Fix (TBody (TVar 1))}], qualType = Fix (TBody (TVar 0))}})

TODO add tests for monotypes

minifyVars :: VarNames a => a -> a Source