disco-0.1.5: Functional programming language for teaching discrete math.
Copyrightdisco team and contributors
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellNone
LanguageHaskell2010

Disco.Typecheck.Solve

Description

Constraint solver for the constraints generated during type checking/inference.

Synopsis

Documentation

data SolveError where Source #

Type of errors which can be generated by the constraint solving process.

Instances

Instances details
Show SolveError Source # 
Instance details

Defined in Disco.Typecheck.Solve

Semigroup SolveError Source # 
Instance details

Defined in Disco.Typecheck.Solve

filterErrors :: Member (Error e) r => [Sem r a] -> Sem r [a] Source #

Run a list of actions, and return the results from those which do not throw an error. If all of them throw an error, rethrow the first one.

asum' :: Member (Error e) r => [Sem r a] -> Sem r a Source #

A variant of asum which picks the first action that succeeds, or re-throws the error of the last one if none of them do. Precondition: the list must not be empty.

data SimpleConstraint where Source #

Constructors

(:<:) :: Type -> Type -> SimpleConstraint 
(:=:) :: Type -> Type -> SimpleConstraint 

Instances

Instances details
Eq SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

Ord SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

Show SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

Generic SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

Associated Types

type Rep SimpleConstraint :: Type -> Type #

Alpha SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

Pretty SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => SimpleConstraint -> Sem r Doc Source #

Subst Type SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

type Rep SimpleConstraint Source # 
Instance details

Defined in Disco.Typecheck.Solve

data TyVarInfo Source #

Information about a particular type variable. More information may be added in the future (e.g. polarity).

Constructors

TVI 

Fields

Instances

Instances details
Show TyVarInfo Source # 
Instance details

Defined in Disco.Typecheck.Solve

Semigroup TyVarInfo Source #

We can learn different things about a type variable from different places; the Semigroup instance allows combining information about a type variable into a single record.

Instance details

Defined in Disco.Typecheck.Solve

Pretty TyVarInfo Source # 
Instance details

Defined in Disco.Typecheck.Solve

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => TyVarInfo -> Sem r Doc Source #

mkTVI :: Ilk -> Sort -> TyVarInfo Source #

Create a TyVarInfo given an Ilk and a Sort.

newtype TyVarInfoMap Source #

A TyVarInfoMap records what we know about each type variable; it is a mapping from type variable names to TyVarInfo records.

Constructors

VM 

Fields

Instances

Instances details
Show TyVarInfoMap Source # 
Instance details

Defined in Disco.Typecheck.Solve

Semigroup TyVarInfoMap Source #

The Semigroup instance for TyVarInfoMap unions the two maps, combining the info records for any variables occurring in both maps.

Instance details

Defined in Disco.Typecheck.Solve

Monoid TyVarInfoMap Source # 
Instance details

Defined in Disco.Typecheck.Solve

Pretty TyVarInfoMap Source # 
Instance details

Defined in Disco.Typecheck.Solve

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => TyVarInfoMap -> Sem r Doc Source #

onVM :: (Map (Name Type) TyVarInfo -> Map (Name Type) TyVarInfo) -> TyVarInfoMap -> TyVarInfoMap Source #

Utility function for acting on a TyVarInfoMap by acting on the underlying Map.

lookupVM :: Name Type -> TyVarInfoMap -> Maybe TyVarInfo Source #

Look up a given variable name in a TyVarInfoMap.

deleteVM :: Name Type -> TyVarInfoMap -> TyVarInfoMap Source #

Remove the mapping for a particular variable name (if it exists) from a TyVarInfoMap.

addSkolems :: [Name Type] -> TyVarInfoMap -> TyVarInfoMap Source #

Given a list of type variable names, add them all to the TyVarInfoMap as Skolem variables (with a trivial sort).

getSort :: TyVarInfoMap -> Name Type -> Sort Source #

Get the sort of a particular variable recorded in a TyVarInfoMap. Returns the trivial (empty) sort for a variable not in the map.

getIlk :: TyVarInfoMap -> Name Type -> Maybe Ilk Source #

Get the Ilk of a variable recorded in a TyVarInfoMap. Returns Nothing if the variable is not in the map, or if its ilk is not known.

extendSort :: Name Type -> Sort -> TyVarInfoMap -> TyVarInfoMap Source #

Extend the sort of a type variable by combining its existing sort with the given one. Has no effect if the variable is not already in the map.

lkup :: (Ord k, Show k, Show (Map k a)) => String -> Map k a -> k -> a Source #

simplify :: Members '[Error SolveError, Output Message, Input TyDefCtx] r => TyVarInfoMap -> [SimpleConstraint] -> Sem r (TyVarInfoMap, [(Atom, Atom)], S) Source #

This step does unification of equality constraints, as well as structural decomposition of subtyping constraints. For example, if we have a constraint (x -> y) (z - Int), then we can decompose it into two constraints, (z <: x) and (y <: Int); if we have a constraint v <: (a,b), then we substitute v ↦ (x,y) (where x and y are fresh type variables) and continue; and so on.

After this step, the remaining constraints will all be atomic constraints, that is, only of the form (v1 <: v2), (v <: b), or (b <: v), where v is a type variable and b is a base type.

mkConstraintGraph :: (Show a, Ord a) => Set a -> [(a, a)] -> Graph a Source #

Given a list of atoms and atomic subtype constraints (each pair (a1,a2) corresponds to the constraint a1 <: a2) build the corresponding constraint graph.

checkSkolems :: Members '[Error SolveError, Output Message, Input TyDefCtx] r => TyVarInfoMap -> Graph Atom -> Sem r (Graph UAtom, S) Source #

Check for any weakly connected components containing more than one skolem, or a skolem and a base type, or a skolem and any variables with nontrivial sorts; such components are not allowed. If there are any WCCs with a single skolem, no base types, and only unsorted variables, just unify them all with the skolem and remove those components.

elimCycles :: Members '[Error SolveError] r => TyDefCtx -> Graph UAtom -> Sem r (Graph UAtom, S) Source #

Eliminate cycles in the constraint set by collapsing each strongly connected component to a single node, (unifying all the types in the SCC). A strongly connected component is a maximal set of nodes where every node is reachable from every other by a directed path; since we are using directed edges to indicate a subtyping constraint, this means every node must be a subtype of every other, and the only way this can happen is if all are in fact equal.

Of course, this step can fail if the types in a SCC are not unifiable. If it succeeds, it returns the collapsed graph (which is now guaranteed to be acyclic, i.e. a DAG) and a substitution.

elimCyclesGen :: forall a b r. (Subst a a, Ord a, Members '[Error SolveError] r) => (Substitution a -> Substitution b) -> ([a] -> Maybe (Substitution a)) -> Graph a -> Sem r (Graph a, Substitution b) Source #

data Rels Source #

Rels stores the set of base types and variables related to a given variable in the constraint graph (either predecessors or successors, but not both).

Constructors

Rels 

Instances

Instances details
Eq Rels Source # 
Instance details

Defined in Disco.Typecheck.Solve

Methods

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

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

Show Rels Source # 
Instance details

Defined in Disco.Typecheck.Solve

Methods

showsPrec :: Int -> Rels -> ShowS #

show :: Rels -> String #

showList :: [Rels] -> ShowS #

newtype RelMap Source #

A RelMap associates each variable to its sets of base type and variable predecessors and successors in the constraint graph.

Constructors

RelMap 

Fields

Instances

Instances details
Pretty RelMap Source # 
Instance details

Defined in Disco.Typecheck.Solve

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => RelMap -> Sem r Doc Source #

substRel :: Name Type -> BaseTy -> RelMap -> RelMap Source #

Modify a RelMap to record the fact that we have solved for a type variable. In particular, delete the variable from the RelMap as a key, and also update the relative sets of every other variable to remove this variable and add the base type we chose for it.

dirtypesBySort :: TyVarInfoMap -> RelMap -> Dir -> BaseTy -> Sort -> Set (Name Type) -> [BaseTy] Source #

Essentially dirtypesBySort vm rm dir t s x finds all the dir-types (sub- or super-) of t which have sort s, relative to the variables in x. This is overbar{T}_S^X (resp. underbar...) from Traytel et al.

limBySort :: TyVarInfoMap -> RelMap -> Dir -> [BaseTy] -> Sort -> Set (Name Type) -> Maybe BaseTy Source #

Sort-aware infimum or supremum.

solveGraph :: Members '[Fresh, Error SolveError, Output Message] r => TyVarInfoMap -> Graph UAtom -> Sem r S Source #

From the constraint graph, build the sets of sub- and super- base types of each type variable, as well as the sets of sub- and supertype variables. For each type variable x in turn, try to find a common supertype of its base subtypes which is consistent with the sort of x and with the sorts of all its sub-variables, as well as symmetrically a common subtype of its supertypes, etc. Assign x one of the two: if it has only successors, assign it their inf; otherwise, assign it the sup of its predecessors. If it has both, we have a choice of whether to assign it the sup of predecessors or inf of successors; both lead to a sound & complete algorithm. We choose to assign it the sup of its predecessors in this case, since it seems nice to default to "simpler" types lower down in the subtyping chain.