License | BSD-3-Clause |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Type inference for the Swarm language. For the approach used here, see https://byorgey.wordpress.com/2021/09/08/implementing-hindley-milner-with-the-unification-fd-library/ .
Synopsis
- data ContextualTypeErr = CTE {}
- data TypeErr
- = UnboundVar Var
- | KindErr KindError
- | EscapedSkolem Var
- | UnificationErr UnificationError
- | Mismatch (Maybe Syntax) TypeJoin
- | LambdaArgMismatch TypeJoin
- | FieldsMismatch (Join (Set Var))
- | DefNotTopLevel Term
- | CantInfer Term
- | CantInferProj Term
- | UnknownProj Var Term
- | InvalidAtomic InvalidAtomicReason Term
- | Impredicative
- data InvalidAtomicReason
- data Source
- withSource :: Source -> a -> a -> a
- data Join a
- getJoin :: Join a -> (a, a)
- data TCFrame where
- data LocatedTCFrame = LocatedTCFrame SrcLoc TCFrame
- type TCStack = [LocatedTCFrame]
- withFrame :: Has (Reader TCStack) sig m => SrcLoc -> TCFrame -> m a -> m a
- fresh :: Has Unification sig m => m UType
- instantiate :: Has Unification sig m => UPolytype -> m UType
- skolemize :: Has Unification sig m => UPolytype -> m UType
- generalize :: (Has Unification sig m, Has (Reader UCtx) sig m) => UType -> m UPolytype
- inferTop :: TCtx -> ReqCtx -> TDCtx -> Syntax -> Either ContextualTypeErr TSyntax
- infer :: (Has (Reader UCtx) sig m, Has (Reader ReqCtx) sig m, Has (Reader TDCtx) sig m, Has (Reader TCStack) sig m, Has Unification sig m, Has (Error ContextualTypeErr) sig m) => Syntax -> m (Syntax' UType)
- inferConst :: Const -> Polytype
- check :: (Has (Reader UCtx) sig m, Has (Reader ReqCtx) sig m, Has (Reader TDCtx) sig m, Has (Reader TCStack) sig m, Has Unification sig m, Has (Error ContextualTypeErr) sig m) => Syntax -> UType -> m (Syntax' UType)
- isSimpleUType :: UType -> Bool
Type errors
data ContextualTypeErr Source #
A type error along with various contextual information to help us generate better error messages.
Instances
Show ContextualTypeErr Source # | |
Defined in Swarm.Language.Typecheck showsPrec :: Int -> ContextualTypeErr -> ShowS # show :: ContextualTypeErr -> String # showList :: [ContextualTypeErr] -> ShowS # |
Errors that can occur during type checking. The idea is that each error carries information that can be used to help explain what went wrong (though the amount of information carried can and should be very much improved in the future); errors can then separately be pretty-printed to display them to the user.
UnboundVar Var | An undefined variable was encountered. |
KindErr KindError | A kind error was encountered. |
EscapedSkolem Var | A Skolem variable escaped its local context. |
UnificationErr UnificationError | Occurs check failure, i.e. infinite type. |
Mismatch (Maybe Syntax) TypeJoin | Type mismatch caught by |
LambdaArgMismatch TypeJoin | Lambda argument type mismatch. |
FieldsMismatch (Join (Set Var)) | Record field mismatch, i.e. based on the expected type we were expecting a record with certain fields, but found one with a different field set. |
DefNotTopLevel Term | A definition was encountered not at the top level. |
CantInfer Term | A term was encountered which we cannot infer the type of. This should never happen. |
CantInferProj Term | We can't infer the type of a record projection |
UnknownProj Var Term | An attempt to project out a nonexistent field |
InvalidAtomic InvalidAtomicReason Term | An invalid argument was provided to |
Impredicative | Some unification variables ended up in a type, probably due to impredicativity. See https://github.com/swarm-game/swarm/issues/351 . |
data InvalidAtomicReason Source #
Various reasons the body of an atomic
might be invalid.
TooManyTicks Int | The argument has too many tangible commands. |
AtomicDupingThing | The argument uses some way to duplicate code: |
NonSimpleVarType Var UPolytype | The argument referred to a variable with a non-simple type. |
NestedAtomic | The argument had a nested |
LongConst | The argument contained a long command |
AtomicSuspend | The argument contained a suspend |
Instances
Show InvalidAtomicReason Source # | |
Defined in Swarm.Language.Typecheck showsPrec :: Int -> InvalidAtomicReason -> ShowS # show :: InvalidAtomicReason -> String # showList :: [InvalidAtomicReason] -> ShowS # | |
PrettyPrec InvalidAtomicReason Source # | |
Defined in Swarm.Language.Pretty prettyPrec :: Int -> InvalidAtomicReason -> Doc ann Source # |
Type provenance
The source of a type during typechecking.
Expected | An expected type that was "pushed down" from the context. |
Actual | An actual/inferred type that was "pulled up" from a term. |
withSource :: Source -> a -> a -> a Source #
A "join" where an expected thing meets an actual thing.
Instances
Foldable Join Source # | |
Defined in Swarm.Language.Typecheck fold :: Monoid m => Join m -> m # foldMap :: Monoid m => (a -> m) -> Join a -> m # foldMap' :: Monoid m => (a -> m) -> Join a -> m # foldr :: (a -> b -> b) -> b -> Join a -> b # foldr' :: (a -> b -> b) -> b -> Join a -> b # foldl :: (b -> a -> b) -> b -> Join a -> b # foldl' :: (b -> a -> b) -> b -> Join a -> b # foldr1 :: (a -> a -> a) -> Join a -> a # foldl1 :: (a -> a -> a) -> Join a -> a # elem :: Eq a => a -> Join a -> Bool # maximum :: Ord a => Join a -> a # | |
Traversable Join Source # | |
Functor Join Source # | |
Show a => Show (Join a) Source # | |
Typechecking stack
A frame to keep track of something we were in the middle of doing during typechecking.
data LocatedTCFrame Source #
A typechecking stack frame together with the relevant SrcLoc
.
Instances
Show LocatedTCFrame Source # | |
Defined in Swarm.Language.Typecheck showsPrec :: Int -> LocatedTCFrame -> ShowS # show :: LocatedTCFrame -> String # showList :: [LocatedTCFrame] -> ShowS # | |
PrettyPrec LocatedTCFrame Source # | |
Defined in Swarm.Language.Pretty prettyPrec :: Int -> LocatedTCFrame -> Doc ann Source # |
type TCStack = [LocatedTCFrame] Source #
A typechecking stack keeps track of what we are currently in the middle of doing during typechecking.
withFrame :: Has (Reader TCStack) sig m => SrcLoc -> TCFrame -> m a -> m a Source #
Push a frame on the typechecking stack.
Typechecking monad
Unification
instantiate :: Has Unification sig m => UPolytype -> m UType Source #
To instantiate
a UPolytype
, we generate a fresh unification
variable for each variable bound by the Forall
, and then
substitute them throughout the type.
skolemize :: Has Unification sig m => UPolytype -> m UType Source #
skolemize
is like instantiate
, except we substitute fresh
type variables instead of unification variables. Such
variables cannot unify with anything other than themselves. This
is used when checking something with a polytype explicitly
specified by the user.
generalize :: (Has Unification sig m, Has (Reader UCtx) sig m) => UType -> m UPolytype Source #
generalize
is the opposite of instantiate
: add a Forall
which closes over all free type and unification variables.
Pick nice type variable names instead of reusing whatever fresh names happened to be used for the free variables.
Type inference
inferTop :: TCtx -> ReqCtx -> TDCtx -> Syntax -> Either ContextualTypeErr TSyntax Source #
Top-level type inference function: given a context of definition types, type synonyms, and a term, either return a type error or a fully type-annotated version of the term.
infer :: (Has (Reader UCtx) sig m, Has (Reader ReqCtx) sig m, Has (Reader TDCtx) sig m, Has (Reader TCStack) sig m, Has Unification sig m, Has (Error ContextualTypeErr) sig m) => Syntax -> m (Syntax' UType) Source #
Infer the type of a term, returning a type-annotated term.
The only cases explicitly handled in infer
are those where
pushing an expected type down into the term can't possibly help,
e.g. most primitives, function application, and binds.
For most everything else we prefer check
because it can often
result in better and more localized type error messages.
Note that we choose to do kind checking inline as we go during typechecking. This has pros and cons. The benefit is that we get to piggyback on the existing source location tracking and typechecking stack, so we can generate better error messages. The downside is that we have to be really careful not to miss any types along the way; there is no difference, at the Haskell type level, between ill- and well-kinded Swarm types, so we just have to make sure that we call checkKind on every type embedded in the term being checked.
inferConst :: Const -> Polytype Source #
Infer the type of a constant.
check :: (Has (Reader UCtx) sig m, Has (Reader ReqCtx) sig m, Has (Reader TDCtx) sig m, Has (Reader TCStack) sig m, Has Unification sig m, Has (Error ContextualTypeErr) sig m) => Syntax -> UType -> m (Syntax' UType) Source #
check t ty
checks that t
has type ty
, returning a
type-annotated AST if so.
We try to stay in checking mode as far as possible, decomposing the expected type as we go and pushing it through the recursion.
isSimpleUType :: UType -> Bool Source #
A simple type is a sum or product of base types.