Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hindley-Milner type inference with ergonomic blame assignment.
blame
is a type-error blame assignment algorithm for languages with Hindley-Milner type inference,
but without generalization of intermediate terms.
This means that it is not suitable for languages with let-generalization.
Let
is an example of a term that is not suitable for this algorithm.
With the contemporary knowledge that "Let Should Not Be Generalised", as argued by luminaries such as Simon Peyton Jones, optimistically this limitation shouldn't apply to new programming languages. This blame assignment algorithm can also be used in a limited sense for existing languages, which do have let-generalization, to provide better type errors in specific definitions which don't happen to use generalizing terms.
The algorithm is pretty simple:
- Invoke all the
inferBody
calls asinfer
normally would, but with one important difference: whereinferBody
would normally get the actual inference results of its child nodes, placeholders are generated in their place - Globally sort all of the tree nodes according to a given node prioritization (this prioritization would be custom for each language)
- According to the order of prioritization,
attempt to unify each infer-result with its placeholder using
inferOfUnify
. If a unification fails, roll back its state changes. The nodes whose unification failed are the ones assigned with type errors.
Lamdu uses this algorithm for its "insist type" feature, which moves around the blame for type mismatches.
Note: If a similar algorithm already existed somewhere, I would very much like to know!
Synopsis
- blame :: forall priority err m exp a. (Ord priority, MonadError err m, Blame m exp) => (a -> priority) -> Tree (InferOf exp) (UVarOf m) -> Tree (Ann a) exp -> m (Tree (BTerm a (UVarOf m)) exp)
- class (Infer m t, RTraversable t, KTraversable (InferOf t), KPointed (InferOf t)) => Blame m t where
- data BTerm a v e = BTerm {}
- type InferOf' e v = Tree (InferOf (GetKnot e)) v
- bAnn :: forall a v e. Lens' (BTerm a v e) a
- bRes :: forall a v e. Lens' (BTerm a v e) (Either (InferOf' e v, InferOf' e v) (InferOf' e v))
- bVal :: forall a v e. Lens' (BTerm a v e) ((#) e (BTerm a v))
- bTermToAnn :: forall a v e r. Recursively KFunctor e => (forall n. KRecWitness e n -> a -> Either (Tree (InferOf n) v, Tree (InferOf n) v) (Tree (InferOf n) v) -> r) -> Tree (BTerm a v) e -> Tree (Ann r) e
Documentation
blame :: forall priority err m exp a. (Ord priority, MonadError err m, Blame m exp) => (a -> priority) -> Tree (InferOf exp) (UVarOf m) -> Tree (Ann a) exp -> m (Tree (BTerm a (UVarOf m)) exp) Source #
Perform Hindley-Milner type inference with prioritised blame for type error, given a prioritisation for the different nodes.
The purpose of the prioritisation is to place the errors in nodes where the resulting errors will be easier to understand.
The expected MonadError
behavior is that catching errors rolls back their state changes
(i.e StateT s (Either e)
is suitable but EitherT e (State s)
is not)
Gets the top-level type for the term for support of recursive definitions, where the top-level type of the term may be in the scope of the inference monad.
class (Infer m t, RTraversable t, KTraversable (InferOf t), KPointed (InferOf t)) => Blame m t where Source #
Class implementing some primitives needed by the blame
algorithm
The blamableRecursive
method represents that Blame
applies to all recursive child nodes.
It replaces context for Blame
to avoid UndecidableSuperClasses
.
inferOfUnify :: Proxy t -> Tree (InferOf t) (UVarOf m) -> Tree (InferOf t) (UVarOf m) -> m () Source #
Unify the types/values in infer results
inferOfMatches :: Proxy t -> Tree (InferOf t) (UVarOf m) -> Tree (InferOf t) (UVarOf m) -> m Bool Source #
Check whether two infer results are the same
blamableRecursive :: Proxy m -> Proxy t -> Dict (KNodesConstraint t (Blame m)) Source #
blamableRecursive :: KNodesConstraint t (Blame m) => Proxy m -> Proxy t -> Dict (KNodesConstraint t (Blame m)) Source #
Instances
type InferOf' e v = Tree (InferOf (GetKnot e)) v Source #
A type synonym to help BTerm
be more succinct