swarm-0.5.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Language.Typecheck

Description

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

Type errors

data ContextualTypeErr Source #

A type error along with various contextual information to help us generate better error messages.

Constructors

CTE 

data TypeErr Source #

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.

Constructors

UnboundVar Var

An undefined variable was encountered.

EscapedSkolem Var

A Skolem variable escaped its local context.

Infinite IntVar UType

Occurs check failure, i.e. infinite type.

UnifyErr (TypeF UType) (TypeF UType)

Error generated by the unifier.

Mismatch (Maybe Syntax) TypeJoin

Type mismatch caught by unifyCheck. The given term was expected to have a certain type, but has a different type instead.

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 r.x if we don't concretely know the type of the record r.

UnknownProj Var Term

An attempt to project out a nonexistent field

InvalidAtomic InvalidAtomicReason Term

An invalid argument was provided to atomic.

Impredicative

Some unification variables ended up in a type, probably due to impredicativity. See https://github.com/swarm-game/swarm/issues/351 .

Instances

Instances details
Show TypeErr Source # 
Instance details

Defined in Swarm.Language.Typecheck

PrettyPrec TypeErr Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

prettyPrec :: Int -> TypeErr -> Doc ann Source #

data InvalidAtomicReason Source #

Various reasons the body of an atomic might be invalid.

Constructors

TooManyTicks Int

The argument has too many tangible commands.

AtomicDupingThing

The argument uses some way to duplicate code: def, let, or lambda.

NonSimpleVarType Var UPolytype

The argument referred to a variable with a non-simple type.

NestedAtomic

The argument had a nested atomic

LongConst

The argument contained a long command

Type provenance

data Source Source #

The source of a type during typechecking.

Constructors

Expected

An expected type that was "pushed down" from the context.

Actual

An actual/inferred type that was "pulled up" from a term.

Instances

Instances details
Bounded Source Source # 
Instance details

Defined in Swarm.Language.Typecheck

Enum Source Source # 
Instance details

Defined in Swarm.Language.Typecheck

Show Source Source # 
Instance details

Defined in Swarm.Language.Typecheck

Eq Source Source # 
Instance details

Defined in Swarm.Language.Typecheck

Methods

(==) :: Source -> Source -> Bool #

(/=) :: Source -> Source -> Bool #

Ord Source Source # 
Instance details

Defined in Swarm.Language.Typecheck

withSource :: Source -> a -> a -> a Source #

Generic eliminator for Source. Choose the first argument if the Source is Expected, and the second argument if Actual.

data Join a Source #

A "join" where an expected thing meets an actual thing.

Instances

Instances details
Show a => Show (Join a) Source # 
Instance details

Defined in Swarm.Language.Typecheck

Methods

showsPrec :: Int -> Join a -> ShowS #

show :: Join a -> String #

showList :: [Join a] -> ShowS #

getJoin :: Join a -> (a, a) Source #

Convert a Join into a pair of (expected, actual).

Typechecking stack

data TCFrame where Source #

A frame to keep track of something we were in the middle of doing during typechecking.

Constructors

TCDef :: Var -> TCFrame

Checking a definition.

TCBindL :: TCFrame

Inferring the LHS of a bind.

TCBindR :: TCFrame

Inferring the RHS of a bind.

Instances

Instances details
Show TCFrame Source # 
Instance details

Defined in Swarm.Language.Typecheck

PrettyPrec TCFrame Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

prettyPrec :: Int -> TCFrame -> Doc ann Source #

data LocatedTCFrame Source #

A typechecking stack frame together with the relevant SrcLoc.

Instances

Instances details
Show LocatedTCFrame Source # 
Instance details

Defined in Swarm.Language.Typecheck

PrettyPrec LocatedTCFrame Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

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 :: SrcLoc -> TCFrame -> TC a -> TC a Source #

Push a frame on the typechecking stack within a local TC computation.

getTCStack :: TC TCStack Source #

Get the current typechecking stack.

Typechecking monad

type TC = ReaderT UCtx (ReaderT TCStack (ExceptT ContextualTypeErr (IntBindingT TypeF Identity))) Source #

The concrete monad used for type checking. IntBindingT is a monad transformer provided by the unification-fd library which supports various operations such as generating fresh variables and unifying things.

Note that we are sort of constrained to use a concrete monad stack by unification-fd, which has some strange types on some of its exported functions that actually require various monad transformers to be stacked in certain ways. For example, see https://hackage.haskell.org/package/unification-fd-0.11.2/docs/Control-Unification.html#v:unify. I don't really see a way to use "capability style" like we do elsewhere in the codebase.

runTC :: TCtx -> TC UModule -> Either ContextualTypeErr TModule Source #

Run a top-level inference computation, returning either a TypeErr or a fully resolved TModule.

fresh :: TC UType Source #

Generate a fresh unification variable.

Unification

substU :: Map (Either Var IntVar) UType -> UType -> UType Source #

Perform a substitution over a UType, substituting for both type and unification variables. Note that since UTypes do not have any binding constructs, we don't have to worry about ignoring bound variables; all variables in a UType are free.

unify :: Maybe Syntax -> TypeJoin -> TC UType Source #

unify t expTy actTy ensures that the given two types are equal. If we know the actual term t which is supposed to have these types, we can use it to generate better error messages.

We first do a quick-and-dirty check to see whether we know for sure the types either are or cannot be equal, generating an equality constraint for the unifier as a last resort.

class HasBindings u where Source #

unification-fd provides a function applyBindings which fully substitutes for any bound unification variables (for efficiency, it does not perform such substitution as it goes along). The HasBindings class is for anything which has unification variables in it and to which we can usefully apply applyBindings.

Methods

applyBindings :: u -> TC u Source #

Instances

Instances details
HasBindings UModule Source # 
Instance details

Defined in Swarm.Language.Typecheck

HasBindings UCtx Source # 
Instance details

Defined in Swarm.Language.Typecheck

HasBindings UPolytype Source # 
Instance details

Defined in Swarm.Language.Typecheck

HasBindings UType Source # 
Instance details

Defined in Swarm.Language.Typecheck

(HasBindings u, Data u) => HasBindings (Syntax' u) Source # 
Instance details

Defined in Swarm.Language.Typecheck

Methods

applyBindings :: Syntax' u -> TC (Syntax' u) Source #

(HasBindings u, Data u) => HasBindings (Term' u) Source # 
Instance details

Defined in Swarm.Language.Typecheck

Methods

applyBindings :: Term' u -> TC (Term' u) Source #

instantiate :: UPolytype -> TC 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 :: UPolytype -> TC 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 :: UType -> TC 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 -> Syntax -> Either ContextualTypeErr TModule Source #

Top-level type inference function: given a context of definition types and a top-level term, either return a type error or its type as a TModule.

inferModule :: Syntax -> TC UModule Source #

Infer the signature of a top-level expression which might contain definitions.

infer :: Syntax -> TC (Syntax' UType) Source #

Infer the type of a term which does not contain definitions, 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.

inferConst :: Const -> Polytype Source #

Infer the type of a constant.

check :: Syntax -> UType -> TC (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.

Orphan instances

Ord IntVar Source #

unification-fd does not provide an Ord instance for IntVar, so we must provide our own, in order to be able to store IntVars in a Set.

Instance details