[commit: ghc] master: Implement QuantifiedConstraints (7df5896)
git at git.haskell.org
git at git.haskell.org
Mon Jun 4 18:24:29 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/7df589608abb178efd6499ee705ba4eebd0cf0d1/ghc
>---------------------------------------------------------------
commit 7df589608abb178efd6499ee705ba4eebd0cf0d1
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Sat Jan 27 14:32:34 2018 +0000
Implement QuantifiedConstraints
We have wanted quantified constraints for ages and, as I hoped,
they proved remarkably simple to implement. All the machinery was
already in place.
The main ticket is Trac #2893, but also relevant are
#5927
#8516
#9123 (especially! higher kinded roles)
#14070
#14317
The wiki page is
https://ghc.haskell.org/trac/ghc/wiki/QuantifiedConstraints
which in turn contains a link to the GHC Proposal where the change
is specified.
Here is the relevant Note:
Note [Quantified constraints]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The -XQuantifiedConstraints extension allows type-class contexts like
this:
data Rose f x = Rose x (f (Rose f x))
instance (Eq a, forall b. Eq b => Eq (f b))
=> Eq (Rose f a) where
(Rose x1 rs1) == (Rose x2 rs2) = x1==x2 && rs1 >= rs2
Note the (forall b. Eq b => Eq (f b)) in the instance contexts.
This quantified constraint is needed to solve the
[W] (Eq (f (Rose f x)))
constraint which arises form the (==) definition.
Here are the moving parts
* Language extension {-# LANGUAGE QuantifiedConstraints #-}
and add it to ghc-boot-th:GHC.LanguageExtensions.Type.Extension
* A new form of evidence, EvDFun, that is used to discharge
such wanted constraints
* checkValidType gets some changes to accept forall-constraints
only in the right places.
* Type.PredTree gets a new constructor ForAllPred, and
and classifyPredType analyses a PredType to decompose
the new forall-constraints
* Define a type TcRnTypes.QCInst, which holds a given
quantified constraint in the inert set
* TcSMonad.InertCans gets an extra field, inert_insts :: [QCInst],
which holds all the Given forall-constraints. In effect,
such Given constraints are like local instance decls.
* When trying to solve a class constraint, via
TcInteract.matchInstEnv, use the InstEnv from inert_insts
so that we include the local Given forall-constraints
in the lookup. (See TcSMonad.getInstEnvs.)
* topReactionsStage calls doTopReactOther for CIrredCan and
CTyEqCan, so they can try to react with any given
quantified constraints (TcInteract.matchLocalInst)
* TcCanonical.canForAll deals with solving a
forall-constraint. See
Note [Solving a Wanted forall-constraint]
Note [Solving a Wanted forall-constraint]
* We augment the kick-out code to kick out an inert
forall constraint if it can be rewritten by a new
type equality; see TcSMonad.kick_out_rewritable
Some other related refactoring
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Move SCC on evidence bindings to post-desugaring, which fixed
#14735, and is generally nicer anyway because we can use
existing CoreSyn free-var functions. (Quantified constraints
made the free-vars of an ev-term a bit more complicated.)
* In LookupInstResult, replace GenInst with OneInst and NotSure,
using the latter for multiple matches and/or one or more
unifiers
>---------------------------------------------------------------
7df589608abb178efd6499ee705ba4eebd0cf0d1
compiler/basicTypes/Id.hs | 2 +-
compiler/deSugar/DsBinds.hs | 42 ++-
compiler/main/DynFlags.hs | 2 +
compiler/specialise/Specialise.hs | 1 +
compiler/typecheck/Inst.hs | 12 +-
compiler/typecheck/TcCanonical.hs | 416 ++++++++++++++++-----
compiler/typecheck/TcErrors.hs | 4 +-
compiler/typecheck/TcEvTerm.hs | 5 +-
compiler/typecheck/TcEvidence.hs | 126 ++++---
compiler/typecheck/TcHsSyn.hs | 39 +-
compiler/typecheck/TcInstDcls.hs | 2 +-
compiler/typecheck/TcInteract.hs | 377 +++++++++++--------
compiler/typecheck/TcMType.hs | 11 +-
compiler/typecheck/TcPatSyn.hs | 7 +-
compiler/typecheck/TcPluginM.hs | 4 +-
compiler/typecheck/TcRnTypes.hs | 67 +++-
compiler/typecheck/TcSMonad.hs | 319 +++++++++++-----
compiler/typecheck/TcSimplify.hs | 2 +-
compiler/typecheck/TcType.hs | 4 +-
compiler/typecheck/TcValidity.hs | 113 ++++--
compiler/types/Class.hs | 54 +--
compiler/types/InstEnv.hs | 75 ++--
compiler/types/Kind.hs | 2 +
compiler/types/Type.hs | 26 +-
docs/users_guide/glasgow_exts.rst | 260 ++++++++++++-
.../ghc-boot-th/GHC/LanguageExtensions/Type.hs | 1 +
testsuite/tests/driver/T4437.hs | 3 +-
.../tests/{ado => quantified-constraints}/Makefile | 0
testsuite/tests/quantified-constraints/T14833.hs | 28 ++
testsuite/tests/quantified-constraints/T14835.hs | 20 +
testsuite/tests/quantified-constraints/T14863.hs | 27 ++
testsuite/tests/quantified-constraints/T14961.hs | 98 +++++
testsuite/tests/quantified-constraints/T2893.hs | 18 +
testsuite/tests/quantified-constraints/T2893a.hs | 27 ++
testsuite/tests/quantified-constraints/T2893c.hs | 15 +
testsuite/tests/quantified-constraints/T9123.hs | 25 ++
testsuite/tests/quantified-constraints/T9123a.hs | 30 ++
testsuite/tests/quantified-constraints/all.T | 10 +
testsuite/tests/rebindable/T5908.hs | 0
testsuite/tests/typecheck/should_compile/T14735.hs | 30 ++
testsuite/tests/typecheck/should_compile/all.T | 2 +
testsuite/tests/typecheck/should_fail/T7019.stderr | 1 +
.../tests/typecheck/should_fail/T7019a.stderr | 1 +
testsuite/tests/typecheck/should_fail/T9196.stderr | 8 +-
44 files changed, 1775 insertions(+), 541 deletions(-)
Diff suppressed because of size. To see it, use:
git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7df589608abb178efd6499ee705ba4eebd0cf0d1
More information about the ghc-commits
mailing list