[commit: ghc] master: Add kind equalities to GHC. (6746549)

git at git.haskell.org git at git.haskell.org
Fri Dec 11 23:22:52 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6746549772c5cc0ac66c0fce562f297f4d4b80a2/ghc

>---------------------------------------------------------------

commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Fri Dec 11 18:19:53 2015 -0500

    Add kind equalities to GHC.
    
    This implements the ideas originally put forward in
    "System FC with Explicit Kind Equality" (ICFP'13).
    
    There are several noteworthy changes with this patch:
     * We now have casts in types. These change the kind
       of a type. See new constructor `CastTy`.
    
     * All types and all constructors can be promoted.
       This includes GADT constructors. GADT pattern matches
       take place in type family equations. In Core,
       types can now be applied to coercions via the
       `CoercionTy` constructor.
    
     * Coercions can now be heterogeneous, relating types
       of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2`
       proves both that `t1` and `t2` are the same and also that
       `k1` and `k2` are the same.
    
     * The `Coercion` type has been significantly enhanced.
       The documentation in `docs/core-spec/core-spec.pdf` reflects
       the new reality.
    
     * The type of `*` is now `*`. No more `BOX`.
    
     * Users can write explicit kind variables in their code,
       anywhere they can write type variables. For backward compatibility,
       automatic inference of kind-variable binding is still permitted.
    
     * The new extension `TypeInType` turns on the new user-facing
       features.
    
     * Type families and synonyms are now promoted to kinds. This causes
       trouble with parsing `*`, leading to the somewhat awkward new
       `HsAppsTy` constructor for `HsType`. This is dispatched with in
       the renamer, where the kind `*` can be told apart from a
       type-level multiplication operator. Without `-XTypeInType` the
       old behavior persists. With `-XTypeInType`, you need to import
       `Data.Kind` to get `*`, also known as `Type`.
    
     * The kind-checking algorithms in TcHsType have been significantly
       rewritten to allow for enhanced kinds.
    
     * The new features are still quite experimental and may be in flux.
    
     * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203.
    
     * TODO: Update user manual.
    
    Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142.
    Updates Haddock submodule.


>---------------------------------------------------------------

6746549772c5cc0ac66c0fce562f297f4d4b80a2
 .gitmodules                                        |   58 +-
 README.md                                          |   90 +-
 compiler/basicTypes/BasicTypes.hs                  |    4 +
 compiler/basicTypes/ConLike.hs                     |    4 +-
 compiler/basicTypes/DataCon.hs                     |  360 ++-
 compiler/basicTypes/DataCon.hs-boot                |    7 +-
 compiler/basicTypes/Id.hs                          |   90 +-
 compiler/basicTypes/IdInfo.hs                      |   20 +-
 compiler/basicTypes/IdInfo.hs-boot                 |    2 +
 compiler/basicTypes/Lexeme.hs                      |    1 -
 compiler/basicTypes/MkId.hs                        |  159 +-
 compiler/basicTypes/MkId.hs-boot                   |    3 +
 compiler/basicTypes/Name.hs                        |    8 +-
 compiler/basicTypes/NameEnv.hs                     |    5 +-
 compiler/basicTypes/OccName.hs                     |    7 +-
 compiler/basicTypes/PatSyn.hs                      |   12 +-
 compiler/basicTypes/PatSyn.hs-boot                 |    2 +-
 compiler/basicTypes/SrcLoc.hs                      |    8 +
 compiler/basicTypes/Unique.hs                      |    9 +-
 compiler/basicTypes/Var.hs                         |   75 +-
 compiler/basicTypes/VarEnv.hs                      |   63 +-
 compiler/basicTypes/VarSet.hs                      |   20 +-
 compiler/cmm/Cmm.hs                                |    0
 compiler/cmm/CmmExpr.hs                            |    0
 compiler/cmm/CmmLayoutStack.hs                     |    0
 compiler/cmm/Hoopl/Dataflow.hs                     |    0
 compiler/codeGen/StgCmmClosure.hs                  |   18 +-
 compiler/codeGen/StgCmmLayout.hs                   |    0
 compiler/coreSyn/CoreArity.hs                      |   49 +-
 compiler/coreSyn/CoreFVs.hs                        |  284 ++-
 compiler/coreSyn/CoreLint.hs                       |  680 +++---
 compiler/coreSyn/CorePrep.hs                       |    9 +-
 compiler/coreSyn/CoreSubst.hs                      |  244 +-
 compiler/coreSyn/CoreSyn.hs                        |   76 +-
 compiler/coreSyn/CoreTidy.hs                       |   11 +-
 compiler/coreSyn/CoreUnfold.hs                     |    1 -
 compiler/coreSyn/CoreUtils.hs                      |   72 +-
 compiler/coreSyn/MkCore.hs                         |   96 +-
 compiler/coreSyn/PprCore.hs                        |    8 +-
 compiler/coreSyn/TrieMap.hs                        |  432 ++--
 compiler/deSugar/Check.hs                          |    2 +-
 compiler/deSugar/Desugar.hs                        |   32 +-
 compiler/deSugar/DsArrows.hs                       |   20 +-
 compiler/deSugar/DsBinds.hs                        |  211 +-
 compiler/deSugar/DsCCall.hs                        |   32 +-
 compiler/deSugar/DsExpr.hs                         |   45 +-
 compiler/deSugar/DsForeign.hs                      |   52 +-
 compiler/deSugar/DsGRHSs.hs                        |    5 +-
 compiler/deSugar/DsListComp.hs                     |  118 +-
 compiler/deSugar/DsMeta.hs                         |   93 +-
 compiler/deSugar/DsMonad.hs                        |    6 +-
 compiler/deSugar/DsUtils.hs                        |   22 +-
 compiler/deSugar/Match.hs                          |   20 +-
 compiler/deSugar/MatchCon.hs                       |   64 +-
 compiler/deSugar/PmExpr.hs                         |    2 +
 compiler/ghc.cabal.in                              |    2 +-
 compiler/ghc.mk                                    |    2 +-
 compiler/ghci/ByteCodeGen.hs                       |   31 +-
 compiler/ghci/Debugger.hs                          |   10 +-
 compiler/ghci/DebuggerUtils.hs                     |    0
 compiler/ghci/RtClosureInspect.hs                  |   59 +-
 compiler/hsSyn/Convert.hs                          |   71 +-
 compiler/hsSyn/HsDecls.hs                          |   16 +-
 compiler/hsSyn/HsExpr.hs                           |    1 -
 compiler/hsSyn/HsPat.hs                            |    9 +-
 compiler/hsSyn/HsTypes.hs                          |  257 +-
 compiler/hsSyn/HsUtils.hs                          |  123 +-
 compiler/iface/BinIface.hs                         |   10 +-
 compiler/iface/BuildTyCl.hs                        |   92 +-
 compiler/iface/IfaceEnv.hs                         |   25 +-
 compiler/iface/IfaceSyn.hs                         |  203 +-
 compiler/iface/IfaceType.hs                        |  633 +++--
 compiler/iface/MkIface.hs                          |   56 +-
 compiler/iface/TcIface.hs                          |  346 ++-
 compiler/iface/TcIface.hs-boot                     |    2 +-
 compiler/main/Annotations.hs                       |    0
 compiler/main/DynFlags.hs                          |    9 +
 compiler/main/DynamicLoading.hs                    |    3 +-
 compiler/main/GHC.hs                               |    9 +-
 compiler/main/GhcMonad.hs                          |    0
 compiler/main/GhcPlugins.hs                        |    4 +-
 compiler/main/HscStats.hs                          |    0
 compiler/main/HscTypes.hs                          |   20 +-
 compiler/main/InteractiveEval.hs                   |   28 +-
 compiler/main/InteractiveEvalTypes.hs              |    2 +-
 compiler/main/PipelineMonad.hs                     |    0
 compiler/main/PprTyThing.hs                        |    4 +-
 compiler/nativeGen/PPC/Ppr.hs                      |    1 -
 compiler/nativeGen/RegAlloc/Graph/ArchBase.hs      |    0
 compiler/nativeGen/RegAlloc/Graph/ArchX86.hs       |    0
 compiler/nativeGen/RegAlloc/Graph/Coalesce.hs      |    0
 compiler/nativeGen/RegAlloc/Graph/Main.hs          |    0
 compiler/nativeGen/RegAlloc/Graph/Spill.hs         |    0
 compiler/nativeGen/RegAlloc/Graph/SpillClean.hs    |    0
 compiler/nativeGen/RegAlloc/Graph/SpillCost.hs     |    0
 compiler/nativeGen/RegAlloc/Graph/Stats.hs         |    0
 compiler/nativeGen/RegAlloc/Linear/Main.hs         |    0
 compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs |    0
 .../nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs    |    0
 compiler/nativeGen/RegAlloc/Linear/StackMap.hs     |    0
 compiler/nativeGen/RegAlloc/Linear/Stats.hs        |    0
 compiler/nativeGen/SPARC/CodeGen/Gen64.hs          |    3 -
 compiler/parser/ApiAnnotation.hs                   |    4 -
 compiler/parser/Lexer.x                            |   10 -
 compiler/parser/Parser.y                           |  222 +-
 compiler/parser/RdrHsSyn.hs                        |   52 +-
 compiler/prelude/PrelInfo.hs                       |   72 +-
 compiler/prelude/PrelNames.hs                      |  147 +-
 compiler/prelude/PrelNames.hs-boot                 |    3 +-
 compiler/prelude/PrelRules.hs                      |   50 +-
 compiler/prelude/PrimOp.hs                         |    6 +-
 compiler/prelude/TysPrim.hs                        |  245 +-
 compiler/prelude/TysWiredIn.hs                     |  396 ++--
 compiler/prelude/TysWiredIn.hs-boot                |   10 +-
 compiler/rename/RnEnv.hs                           |   21 +-
 compiler/rename/RnNames.hs                         |    2 +-
 compiler/rename/RnPat.hs                           |    4 +-
 compiler/rename/RnSource.hs                        |   98 +-
 compiler/rename/RnTypes.hs                         |  832 ++++---
 compiler/simplCore/CSE.hs                          |    4 +-
 compiler/simplCore/CoreMonad.hs                    |    1 -
 compiler/simplCore/FloatIn.hs                      |  169 +-
 compiler/simplCore/OccurAnal.hs                    |    2 +-
 compiler/simplCore/SAT.hs                          |    2 +-
 compiler/simplCore/SetLevels.hs                    |   30 +-
 compiler/simplCore/SimplEnv.hs                     |   64 +-
 compiler/simplCore/SimplMonad.hs                   |    4 +-
 compiler/simplCore/SimplUtils.hs                   |   17 +-
 compiler/simplCore/Simplify.hs                     |   76 +-
 compiler/simplStg/UnariseStg.hs                    |    2 +-
 compiler/specialise/Rules.hs                       |   54 +-
 compiler/specialise/SpecConstr.hs                  |   10 +-
 compiler/specialise/Specialise.hs                  |   60 +-
 compiler/stgSyn/StgLint.hs                         |    1 -
 compiler/stranal/DmdAnal.hs                        |    4 +-
 compiler/stranal/WwLib.hs                          |   39 +-
 compiler/typecheck/FamInst.hs                      |  120 +-
 compiler/typecheck/FunDeps.hs                      |   60 +-
 compiler/typecheck/Inst.hs                         |  170 +-
 compiler/typecheck/TcArrows.hs                     |   18 +-
 compiler/typecheck/TcBinds.hs                      |  139 +-
 compiler/typecheck/TcCanonical.hs                  |  570 +++--
 compiler/typecheck/TcClassDcl.hs                   |   20 +-
 compiler/typecheck/TcDefaults.hs                   |    5 +-
 compiler/typecheck/TcDeriv.hs                      |  204 +-
 compiler/typecheck/TcEnv.hs                        |   37 +-
 compiler/typecheck/TcErrors.hs                     |  418 ++--
 compiler/typecheck/TcEvidence.hs                   |  663 ++----
 compiler/typecheck/TcExpr.hs                       |  130 +-
 compiler/typecheck/TcFlatten.hs                    |  263 ++-
 compiler/typecheck/TcForeign.hs                    |   55 +-
 compiler/typecheck/TcGenDeriv.hs                   |   31 +-
 compiler/typecheck/TcGenGenerics.hs                |   31 +-
 compiler/typecheck/TcHsSyn.hs                      |  309 ++-
 compiler/typecheck/TcHsType.hs                     | 2078 +++++++++-------
 compiler/typecheck/TcInstDcls.hs                   |   87 +-
 compiler/typecheck/TcInteract.hs                   |  291 ++-
 compiler/typecheck/TcMType.hs                      |  741 ++++--
 compiler/typecheck/TcMatches.hs                    |   20 +-
 compiler/typecheck/TcPat.hs                        |   72 +-
 compiler/typecheck/TcPatSyn.hs                     |   53 +-
 compiler/typecheck/TcPluginM.hs                    |   64 +-
 compiler/typecheck/TcRnDriver.hs                   |   41 +-
 compiler/typecheck/TcRnMonad.hs                    |   60 +-
 compiler/typecheck/TcRnTypes.hs                    |  335 ++-
 compiler/typecheck/TcRules.hs                      |  140 +-
 compiler/typecheck/TcSMonad.hs                     |  642 ++---
 compiler/typecheck/TcSimplify.hs                   |  599 +++--
 compiler/typecheck/TcSplice.hs                     |  178 +-
 compiler/typecheck/TcTyClsDecls.hs                 | 1099 ++++++---
 compiler/typecheck/TcTyDecls.hs                    |  229 +-
 compiler/typecheck/TcType.hs                       |  990 +++++---
 compiler/typecheck/TcType.hs-boot                  |    1 +
 compiler/typecheck/TcTypeNats.hs                   |  111 +-
 compiler/typecheck/TcTypeable.hs                   |    5 +-
 compiler/typecheck/TcUnify.hs                      |  724 +++---
 compiler/typecheck/TcUnify.hs-boot                 |    7 +-
 compiler/typecheck/TcValidity.hs                   |  702 ++++--
 compiler/types/Class.hs                            |   20 +-
 compiler/types/CoAxiom.hs                          |   34 +-
 compiler/types/Coercion.hs                         | 2495 +++++++++----------
 compiler/types/Coercion.hs-boot                    |   46 +
 compiler/types/FamInstEnv.hs                       |  511 +++-
 compiler/types/InstEnv.hs                          |   24 +-
 compiler/types/Kind.hs                             |  297 +--
 compiler/types/OptCoercion.hs                      |  568 +++--
 compiler/types/TyCoRep.hs                          | 2496 ++++++++++++++++++++
 .../types/{TypeRep.hs-boot => TyCoRep.hs-boot}     |    9 +-
 compiler/types/TyCon.hs                            |  211 +-
 compiler/types/Type.hs                             | 1895 +++++++++------
 compiler/types/Type.hs-boot                        |   15 +-
 compiler/types/TypeRep.hs                          | 1020 --------
 compiler/types/Unify.hs                            | 1237 ++++++----
 compiler/utils/Bag.hs                              |    2 +-
 compiler/utils/ListSetOps.hs                       |   15 +-
 compiler/utils/MonadUtils.hs                       |   24 +-
 compiler/utils/Outputable.hs                       |   17 +-
 compiler/utils/Pair.hs                             |   12 +-
 compiler/utils/Serialized.hs                       |    0
 compiler/utils/UniqDFM.hs                          |    4 +
 compiler/utils/UniqDSet.hs                         |   15 +-
 compiler/utils/UniqSet.hs                          |    2 +-
 compiler/utils/Util.hs                             |   49 +-
 compiler/vectorise/Vectorise.hs                    |    0
 compiler/vectorise/Vectorise/Builtins.hs           |    0
 compiler/vectorise/Vectorise/Builtins/Base.hs      |    0
 .../vectorise/Vectorise/Builtins/Initialise.hs     |    2 +-
 compiler/vectorise/Vectorise/Convert.hs            |   15 +-
 compiler/vectorise/Vectorise/Env.hs                |    6 +-
 compiler/vectorise/Vectorise/Exp.hs                |   60 +-
 .../vectorise/Vectorise/Generic/Description.hs     |    0
 compiler/vectorise/Vectorise/Generic/PADict.hs     |    2 +-
 compiler/vectorise/Vectorise/Generic/PAMethods.hs  |   18 +-
 compiler/vectorise/Vectorise/Generic/PData.hs      |   14 +-
 compiler/vectorise/Vectorise/Monad.hs              |    0
 compiler/vectorise/Vectorise/Monad/Base.hs         |    0
 compiler/vectorise/Vectorise/Monad/Global.hs       |    0
 compiler/vectorise/Vectorise/Monad/InstEnv.hs      |    0
 compiler/vectorise/Vectorise/Monad/Local.hs        |    6 +-
 compiler/vectorise/Vectorise/Monad/Naming.hs       |   11 +-
 compiler/vectorise/Vectorise/Type/Classify.hs      |   21 +-
 compiler/vectorise/Vectorise/Type/Env.hs           |    0
 compiler/vectorise/Vectorise/Type/TyConDecl.hs     |   12 +-
 compiler/vectorise/Vectorise/Type/Type.hs          |   15 +-
 compiler/vectorise/Vectorise/Utils.hs              |    0
 compiler/vectorise/Vectorise/Utils/Base.hs         |    0
 compiler/vectorise/Vectorise/Utils/Closure.hs      |    0
 compiler/vectorise/Vectorise/Utils/Hoisting.hs     |    0
 compiler/vectorise/Vectorise/Utils/PADict.hs       |   21 +-
 compiler/vectorise/Vectorise/Utils/Poly.hs         |    0
 compiler/vectorise/Vectorise/Var.hs                |    0
 compiler/vectorise/Vectorise/Vect.hs               |    0
 docs/core-spec/.gitignore                          |    1 +
 docs/core-spec/CoreLint.ott                        |  309 ++-
 docs/core-spec/CoreSyn.ott                         |  219 +-
 docs/core-spec/Makefile                            |    2 +-
 docs/core-spec/OpSem.ott                           |    6 +-
 docs/core-spec/core-spec.mng                       |   83 +-
 docs/core-spec/core-spec.pdf                       |  Bin 342464 -> 348408 bytes
 docs/users_guide/glasgow_exts.rst                  |    3 -
 docs/users_guide/using.rst                         |   19 +-
 libraries/base/Data/Coerce.hs                      |    3 +-
 libraries/base/Data/Kind.hs                        |   19 +
 libraries/base/Data/Monoid.hs                      |    1 -
 libraries/base/Data/Type/Coercion.hs               |   10 +-
 libraries/base/Data/Type/Equality.hs               |   40 +-
 libraries/base/Data/Typeable/Internal.hs           |   48 +-
 libraries/base/GHC/Base.hs                         |   19 +-
 libraries/base/GHC/Exts.hs                         |   11 +-
 libraries/base/GHC/TypeLits.hs                     |    2 -
 libraries/base/base.cabal                          |    1 +
 libraries/base/tests/CatEntail.hs                  |    2 +-
 libraries/ghc-prim/GHC/Classes.hs                  |    1 -
 libraries/ghc-prim/GHC/Types.hs                    |   62 +-
 rae.txt                                            |  319 +++
 testsuite/tests/ado/ado004.stderr                  |    4 +-
 .../tests/annotations/should_fail/annfail10.stderr |    2 +-
 .../tests/deSugar/should_compile/T2431.stderr      |   22 +-
 .../tests/deSugar/should_compile/T4488.stderr      |   32 +-
 testsuite/tests/{ado => dependent}/Makefile        |    0
 testsuite/tests/dependent/should_compile/Dep1.hs   |   13 +
 testsuite/tests/dependent/should_compile/Dep2.hs   |    7 +
 testsuite/tests/dependent/should_compile/Dep3.hs   |   26 +
 .../dependent/should_compile/KindEqualities.hs     |   25 +
 .../dependent/should_compile/KindEqualities2.hs    |   43 +
 .../tests/dependent/should_compile/KindLevels.hs   |    9 +
 .../should_compile/Makefile                        |    0
 .../tests/dependent/should_compile/RAE_T32b.hs     |   23 +
 testsuite/tests/dependent/should_compile/Rae31.hs  |   24 +
 .../tests/dependent/should_compile/RaeBlogPost.hs  |   63 +
 testsuite/tests/dependent/should_compile/all.T     |   10 +
 .../tests/dependent/should_compile/mkGADTVars.hs   |    9 +
 .../tests/dependent/should_fail/BadTelescope.hs    |    9 +
 .../dependent/should_fail/BadTelescope.stderr      |    9 +
 .../tests/dependent/should_fail/BadTelescope2.hs   |   14 +
 .../dependent/should_fail/BadTelescope2.stderr     |   16 +
 .../tests/dependent/should_fail/BadTelescope3.hs   |    9 +
 .../dependent/should_fail/BadTelescope3.stderr     |    6 +
 .../tests/dependent/should_fail/BadTelescope4.hs   |   13 +
 .../dependent/should_fail/BadTelescope4.stderr     |   15 +
 testsuite/tests/dependent/should_fail/DepFail1.hs  |   11 +
 .../tests/dependent/should_fail/DepFail1.stderr    |   12 +
 testsuite/tests/dependent/should_fail/Makefile     |    5 +
 .../tests/dependent/should_fail/PromotedClass.hs   |   11 +
 .../dependent/should_fail/PromotedClass.stderr     |    6 +
 testsuite/tests/dependent/should_fail/RAE_T32a.hs  |   35 +
 .../tests/dependent/should_fail/RAE_T32a.stderr    |   19 +
 testsuite/tests/dependent/should_fail/SelfDep.hs   |    3 +
 .../tests/dependent/should_fail/SelfDep.stderr     |    5 +
 .../tests/dependent/should_fail/TypeSkolEscape.hs  |    8 +
 .../dependent/should_fail/TypeSkolEscape.stderr    |    7 +
 testsuite/tests/dependent/should_fail/all.T        |    9 +
 .../{should_fail => should_compile}/T10524.hs      |    1 +
 testsuite/tests/deriving/should_compile/all.T      |    1 +
 testsuite/tests/deriving/should_fail/T1496.stderr  |    8 +-
 testsuite/tests/deriving/should_fail/T7959.stderr  |   12 +-
 testsuite/tests/deriving/should_fail/all.T         |    1 -
 .../tests/deriving/should_fail/drvfail005.stderr   |    9 +-
 testsuite/tests/driver/T4437.hs                    |    3 +-
 testsuite/tests/driver/werror.stderr               |    2 +-
 testsuite/tests/gadt/T3163.stderr                  |    2 +-
 testsuite/tests/gadt/gadt-escape1.stderr           |   32 +-
 testsuite/tests/gadt/gadt10.stderr                 |    4 +-
 testsuite/tests/gadt/gadt13.stderr                 |   30 +-
 testsuite/tests/gadt/gadt7.stderr                  |   34 +-
 testsuite/tests/ghc-api/annotations/T10307.stdout  |    1 -
 testsuite/tests/ghc-api/annotations/T10312.stderr  |    0
 testsuite/tests/ghc-api/annotations/T10312.stdout  |    2 -
 testsuite/tests/ghc-api/annotations/T10357.stderr  |   14 +-
 testsuite/tests/ghc-api/annotations/T10357.stdout  |    1 -
 testsuite/tests/ghc-api/annotations/T10358.stdout  |    5 -
 testsuite/tests/ghc-api/annotations/T11018.stderr  |    2 +-
 testsuite/tests/ghc-api/annotations/T11018.stdout  |    6 +-
 .../tests/ghc-api/annotations/exampleTest.stdout   |    3 +-
 .../tests/ghc-api/annotations/listcomps.stdout     |    2 -
 .../tests/ghc-api/annotations/parseTree.stdout     |    4 +-
 testsuite/tests/ghc-api/landmines/landmines.stdout |    4 +-
 .../tests/ghci.debugger/scripts/break001.stdout    |    4 +-
 .../tests/ghci.debugger/scripts/break003.stderr    |    2 +-
 .../tests/ghci.debugger/scripts/break003.stdout    |    8 +-
 .../tests/ghci.debugger/scripts/break006.stderr    |   16 +-
 .../tests/ghci.debugger/scripts/break006.stdout    |   12 +-
 .../tests/ghci.debugger/scripts/break012.stdout    |   10 +-
 .../tests/ghci.debugger/scripts/break018.stdout    |    4 +-
 .../ghci.debugger/scripts/break022/break022.stdout |    2 +-
 .../tests/ghci.debugger/scripts/break026.stdout    |   40 +-
 .../tests/ghci.debugger/scripts/break028.stdout    |    6 +-
 .../tests/ghci.debugger/scripts/hist001.stdout     |   22 +-
 .../tests/ghci.debugger/scripts/print018.stdout    |    6 +-
 .../tests/ghci.debugger/scripts/print022.stdout    |    6 +-
 .../tests/ghci.debugger/scripts/print025.stdout    |    2 +-
 .../tests/ghci.debugger/scripts/print031.stdout    |    2 +-
 .../tests/ghci.debugger/scripts/print036.stdout    |    1 -
 testsuite/tests/ghci/prog009/ghci.prog009.stdout   |    0
 testsuite/tests/ghci/scripts/Defer02.stderr        |    7 +-
 testsuite/tests/ghci/scripts/Defer02.stdout        |    2 +-
 testsuite/tests/ghci/scripts/T10122.stdout         |    2 +-
 testsuite/tests/ghci/scripts/T10508.stderr         |    6 +-
 testsuite/tests/ghci/scripts/T2182ghci.stderr      |   10 +-
 testsuite/tests/ghci/scripts/T4087.stdout          |    2 +-
 testsuite/tests/ghci/scripts/T4175.stdout          |   15 +-
 testsuite/tests/ghci/scripts/T6018ghcifail.stderr  |    6 +-
 testsuite/tests/ghci/scripts/T7627.stdout          |    6 +-
 testsuite/tests/ghci/scripts/T7730.stdout          |    2 +-
 testsuite/tests/ghci/scripts/T7873.script          |    5 +-
 testsuite/tests/ghci/scripts/T7873.stderr          |    7 +
 testsuite/tests/ghci/scripts/T7873.stdout          |    8 +-
 testsuite/tests/ghci/scripts/T7939.stdout          |   35 +-
 testsuite/tests/ghci/scripts/T9181.stdout          |   24 +-
 testsuite/tests/ghci/scripts/ghci001.stdout        |    0
 testsuite/tests/ghci/scripts/ghci013.stdout        |    2 +-
 testsuite/tests/ghci/scripts/ghci047.stderr        |   26 +-
 testsuite/tests/ghci/scripts/ghci051.stderr        |    4 +-
 testsuite/tests/ghci/scripts/ghci055.stdout        |    4 +-
 testsuite/tests/ghci/scripts/ghci059.script        |    2 +-
 testsuite/tests/ghci/scripts/ghci059.stdout        |    2 +-
 .../should_compile_flag_haddock/haddockA023.stderr |    2 +-
 .../should_compile_flag_haddock/haddockA026.stderr |    2 +-
 .../should_compile_flag_haddock/haddockA027.stderr |    4 +-
 .../should_compile_flag_haddock/haddockA028.stderr |    2 +-
 .../should_compile/PushedInAsGivens.stderr         |    3 +-
 .../tests/indexed-types/should_compile/Simple12.hs |    1 -
 .../indexed-types/should_compile/T3017.stderr      |    5 +-
 .../indexed-types/should_compile/T3208b.stderr     |    3 +-
 .../tests/indexed-types/should_compile/T9316.hs    |    1 -
 .../tests/indexed-types/should_compile/T9747.hs    |    2 +-
 .../indexed-types/should_fail/ClosedFam3.stderr    |   24 +-
 .../indexed-types/should_fail/Overlap4.stderr      |    1 +
 .../indexed-types/should_fail/SimpleFail12.stderr  |    2 +-
 .../indexed-types/should_fail/SimpleFail14.stderr  |    8 +-
 .../indexed-types/should_fail/SimpleFail1a.stderr  |    7 +-
 .../indexed-types/should_fail/SimpleFail1b.stderr  |    4 +-
 .../indexed-types/should_fail/SimpleFail6.stderr   |    4 +-
 .../tests/indexed-types/should_fail/T10141.stderr  |    5 +-
 .../tests/indexed-types/should_fail/T10899.stderr  |    2 +-
 .../tests/indexed-types/should_fail/T2627b.stderr  |   13 +-
 .../tests/indexed-types/should_fail/T2664.stderr   |   34 +-
 .../tests/indexed-types/should_fail/T3330a.stderr  |   16 +-
 .../tests/indexed-types/should_fail/T3330c.stderr  |   23 +-
 .../tests/indexed-types/should_fail/T4179.stderr   |   22 +-
 .../tests/indexed-types/should_fail/T5439.stderr   |   46 +-
 .../tests/indexed-types/should_fail/T6123.stderr   |   12 +-
 .../tests/indexed-types/should_fail/T7786.stderr   |   64 +-
 .../tests/indexed-types/should_fail/T7788.stderr   |    6 +-
 .../tests/indexed-types/should_fail/T9160.stderr   |    2 +-
 .../tests/indexed-types/should_fail/T9171.stderr   |   17 +-
 .../tests/indexed-types/should_fail/T9357.stderr   |    2 +-
 testsuite/tests/indexed-types/should_run/T5719.hs  |    2 +-
 testsuite/tests/mdo/should_compile/mdo006.hs       |    0
 testsuite/tests/module/mod71.stderr                |   20 +-
 testsuite/tests/module/mod72.stderr                |    2 +-
 .../tests/parser/should_compile/read014.stderr     |    2 +-
 testsuite/tests/parser/should_fail/T3811d.stderr   |    2 +-
 testsuite/tests/parser/should_fail/T7848.stderr    |    4 +-
 .../tests/parser/should_fail/readFail003.stderr    |   30 +-
 .../tests/partial-sigs/should_compile/ADT.stderr   |    2 +-
 .../should_compile/DataFamilyInstanceLHS.stderr    |    2 +-
 .../partial-sigs/should_compile/Meltdown.stderr    |    2 +-
 .../partial-sigs/should_compile/SkipMany.stderr    |    2 +-
 .../partial-sigs/should_compile/T10403.stderr      |   14 +-
 .../partial-sigs/should_compile/T10438.stderr      |   16 +-
 .../partial-sigs/should_compile/T11192.stderr      |    4 +-
 .../should_compile/TypeFamilyInstanceLHS.stderr    |    3 +-
 .../WarningWildcardInstantiations.stderr           |   26 +-
 .../tests/partial-sigs/should_fail/T10045.stderr   |    4 +-
 .../should_fail/WildcardInstantiations.stderr      |   24 +-
 testsuite/tests/patsyn/should_fail/T9161-2.stderr  |    7 +-
 testsuite/tests/perf/compiler/all.T                |   42 +-
 testsuite/tests/perf/haddock/all.T                 |    6 +-
 testsuite/tests/polykinds/PolyInstances.hs         |   22 +
 testsuite/tests/polykinds/PolyKinds02.stderr       |    7 +-
 testsuite/tests/polykinds/PolyKinds04.stderr       |    5 +-
 testsuite/tests/polykinds/PolyKinds07.stderr       |    2 +-
 testsuite/tests/polykinds/SigTvKinds.hs            |    7 +
 testsuite/tests/polykinds/SigTvKinds2.hs           |    7 +
 testsuite/tests/polykinds/SigTvKinds2.stderr       |    6 +
 testsuite/tests/polykinds/T10503.stderr            |   29 +-
 testsuite/tests/polykinds/T11142.hs                |   10 +
 testsuite/tests/polykinds/T11142.stderr            |    7 +
 testsuite/tests/polykinds/T5716.hs                 |    0
 testsuite/tests/polykinds/T5716.stderr             |    9 +-
 testsuite/tests/polykinds/T6021.hs                 |    2 +-
 testsuite/tests/polykinds/T6021.stderr             |    5 +-
 testsuite/tests/polykinds/T6039.stderr             |    4 -
 testsuite/tests/polykinds/T6129.stderr             |    2 +-
 testsuite/tests/polykinds/T7224.stderr             |    9 +-
 testsuite/tests/polykinds/T7230.stderr             |    6 +-
 testsuite/tests/polykinds/T7278.hs                 |    3 +-
 testsuite/tests/polykinds/T7278.stderr             |    9 +-
 testsuite/tests/polykinds/T7328.hs                 |    2 +-
 testsuite/tests/polykinds/T7328.stderr             |   11 +-
 testsuite/tests/polykinds/T7341.hs                 |    2 +-
 testsuite/tests/polykinds/T7341.stderr             |    4 +-
 testsuite/tests/polykinds/T7404.stderr             |    7 +-
 testsuite/tests/polykinds/T7438.stderr             |   35 +-
 testsuite/tests/polykinds/T7481.stderr             |    4 -
 testsuite/tests/polykinds/T7524.stderr             |    6 +-
 testsuite/tests/polykinds/T7594.hs                 |    4 +-
 testsuite/tests/polykinds/T7805.stderr             |    8 +-
 testsuite/tests/polykinds/T7939a.stderr            |    5 +-
 testsuite/tests/polykinds/T8566.stderr             |   35 +-
 testsuite/tests/polykinds/T8616.stderr             |   14 +-
 testsuite/tests/polykinds/T9200b.stderr            |    7 +-
 testsuite/tests/polykinds/T9222.stderr             |   32 +-
 testsuite/tests/polykinds/T9569.hs                 |    2 +-
 testsuite/tests/polykinds/all.T                    |   10 +-
 testsuite/tests/rename/should_fail/T2993.stderr    |    2 +-
 .../tests/rename/should_fail/rnfail026.stderr      |   15 +-
 .../tests/rename/should_fail/rnfail055.stderr      |    3 +-
 testsuite/tests/roles/should_compile/Roles1.stderr |   84 +-
 .../tests/roles/should_compile/Roles13.stderr      |   34 +-
 .../tests/roles/should_compile/Roles14.stderr      |    9 +-
 testsuite/tests/roles/should_compile/Roles2.stderr |   18 +-
 testsuite/tests/roles/should_compile/Roles3.stderr |   38 +-
 testsuite/tests/roles/should_compile/Roles4.stderr |   16 +-
 testsuite/tests/roles/should_compile/T8958.stderr  |    6 +-
 testsuite/tests/roles/should_compile/all.T         |   10 +-
 testsuite/tests/rts/T9045.hs                       |    1 +
 testsuite/tests/simplCore/should_compile/Makefile  |    2 +-
 .../tests/simplCore/should_compile/T7360.stderr    |   58 +-
 .../tests/simplCore/should_compile/T8274.stdout    |   10 +-
 .../tests/simplCore/should_compile/T9400.stderr    |    6 +-
 .../tests/simplCore/should_compile/rule2.stderr    |    4 +-
 .../simplCore/should_compile/spec-inline.stderr    |    7 +-
 testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr   |    2 +
 testsuite/tests/stranal/sigs/T8569.stderr          |    2 +
 testsuite/tests/th/T3177a.stderr                   |   14 +-
 testsuite/tests/th/T3920.hs                        |    0
 testsuite/tests/th/T7021a.hs                       |    2 +-
 testsuite/tests/th/T8953.stderr                    |    4 +-
 testsuite/tests/th/TH_RichKinds.hs                 |    2 +-
 testsuite/tests/th/TH_RichKinds.stderr             |    4 +-
 testsuite/tests/th/TH_Roles2.stderr                |    1 +
 testsuite/tests/typecheck/should_compile/T5581.hs  |    2 +-
 testsuite/tests/typecheck/should_compile/T5655.hs  |    2 +-
 .../tests/typecheck/should_compile/T9834.stderr    |  126 +-
 .../tests/typecheck/should_compile/T9939.stderr    |   24 +-
 .../tests/typecheck/should_compile/tc141.stderr    |   20 +-
 .../tests/typecheck/should_compile/tc167.stderr    |    1 +
 .../tests/typecheck/should_compile/tc211.stderr    |   20 +-
 .../tests/typecheck/should_compile/tc231.stderr    |    4 +-
 .../tests/typecheck/should_compile/tc243.stderr    |    2 +-
 testsuite/tests/typecheck/should_compile/tc255.hs  |    2 +-
 testsuite/tests/typecheck/should_compile/tc256.hs  |    2 +-
 testsuite/tests/typecheck/should_compile/tc257.hs  |    2 +-
 testsuite/tests/typecheck/should_compile/tc258.hs  |    2 +-
 .../typecheck/should_fail/AssocTyDef04.stderr      |    2 +-
 .../tests/typecheck/should_fail/AssocTyDef06.hs    |    2 +-
 .../typecheck/should_fail/AssocTyDef06.stderr      |    9 +-
 .../typecheck/should_fail/FrozenErrorTests.stderr  |   87 +-
 .../tests/typecheck/should_fail/T10285.stderr      |    2 +-
 .../tests/typecheck/should_fail/T11112.stderr      |    2 +-
 testsuite/tests/typecheck/should_fail/T1633.hs     |    2 +
 testsuite/tests/typecheck/should_fail/T1633.stderr |    6 +-
 testsuite/tests/typecheck/should_fail/T2994.stderr |   32 +-
 testsuite/tests/typecheck/should_fail/T3540.stderr |   22 +-
 testsuite/tests/typecheck/should_fail/T3950.stderr |   22 +-
 testsuite/tests/typecheck/should_fail/T4875.stderr |    8 +-
 testsuite/tests/typecheck/should_fail/T5570.stderr |   12 +-
 testsuite/tests/typecheck/should_fail/T5853.stderr |   35 +-
 .../tests/typecheck/should_fail/T6018fail.stderr   |    8 +-
 .../typecheck/should_fail/T6018failclosed.stderr   |   13 +-
 testsuite/tests/typecheck/should_fail/T7368.stderr |   12 +-
 .../tests/typecheck/should_fail/T7368a.stderr      |   20 +-
 testsuite/tests/typecheck/should_fail/T7410.stderr |    8 +-
 testsuite/tests/typecheck/should_fail/T7453.stderr |   64 +-
 testsuite/tests/typecheck/should_fail/T7609.stderr |   19 +-
 testsuite/tests/typecheck/should_fail/T7645.stderr |    8 +-
 testsuite/tests/typecheck/should_fail/T7696.stderr |    4 +-
 testsuite/tests/typecheck/should_fail/T7734.stderr |   28 +-
 testsuite/tests/typecheck/should_fail/T7778.stderr |   13 +-
 testsuite/tests/typecheck/should_fail/T7857.stderr |   30 +-
 testsuite/tests/typecheck/should_fail/T7892.stderr |    2 +-
 testsuite/tests/typecheck/should_fail/T8030.stderr |    6 +-
 testsuite/tests/typecheck/should_fail/T8262.stderr |   14 +-
 testsuite/tests/typecheck/should_fail/T8514.stderr |    3 +-
 testsuite/tests/typecheck/should_fail/T8603.stderr |   12 +-
 testsuite/tests/typecheck/should_fail/T8806.stderr |   20 +-
 testsuite/tests/typecheck/should_fail/T9109.stderr |   27 +-
 testsuite/tests/typecheck/should_fail/T9196.stderr |   15 +-
 testsuite/tests/typecheck/should_fail/T9201.stderr |    9 +-
 testsuite/tests/typecheck/should_fail/T9260.stderr |   10 +-
 testsuite/tests/typecheck/should_fail/T9999.stderr |   15 +-
 .../typecheck/should_fail/TcCoercibleFail.stderr   |  100 +-
 .../typecheck/should_fail/TcCoercibleFail2.hs      |    2 +
 .../typecheck/should_fail/TcCoercibleFail2.stderr  |    4 +-
 .../tests/typecheck/should_fail/tcfail002.stderr   |   14 +-
 .../tests/typecheck/should_fail/tcfail004.stderr   |   16 +-
 .../tests/typecheck/should_fail/tcfail005.stderr   |   16 +-
 .../tests/typecheck/should_fail/tcfail010.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail013.stderr   |   11 +-
 .../tests/typecheck/should_fail/tcfail014.stderr   |   14 +-
 .../tests/typecheck/should_fail/tcfail018.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail032.stderr   |   24 +-
 testsuite/tests/typecheck/should_fail/tcfail036.hs |    2 +
 .../tests/typecheck/should_fail/tcfail036.stderr   |   10 +-
 .../tests/typecheck/should_fail/tcfail049.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail050.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail057.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail070.stderr   |    3 +-
 .../tests/typecheck/should_fail/tcfail078.stderr   |    6 +-
 .../tests/typecheck/should_fail/tcfail088.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail090.stderr   |   10 +-
 .../tests/typecheck/should_fail/tcfail099.stderr   |   26 +-
 .../tests/typecheck/should_fail/tcfail113.stderr   |   20 +-
 .../tests/typecheck/should_fail/tcfail122.stderr   |   29 +-
 .../tests/typecheck/should_fail/tcfail123.stderr   |    6 +-
 .../tests/typecheck/should_fail/tcfail132.stderr   |   13 +-
 .../tests/typecheck/should_fail/tcfail133.stderr   |    8 +-
 .../tests/typecheck/should_fail/tcfail140.stderr   |   58 +-
 .../tests/typecheck/should_fail/tcfail146.stderr   |    8 +-
 .../tests/typecheck/should_fail/tcfail147.stderr   |    4 +-
 .../tests/typecheck/should_fail/tcfail151.stderr   |    7 +
 .../tests/typecheck/should_fail/tcfail159.stderr   |    6 +-
 .../tests/typecheck/should_fail/tcfail160.stderr   |    7 +-
 .../tests/typecheck/should_fail/tcfail161.stderr   |    7 +-
 .../tests/typecheck/should_fail/tcfail181.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail184.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail195.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail196.stderr   |    5 +-
 .../tests/typecheck/should_fail/tcfail197.stderr   |    7 +-
 .../tests/typecheck/should_fail/tcfail200.stderr   |   14 +-
 .../tests/typecheck/should_fail/tcfail201.stderr   |    2 +-
 .../tests/typecheck/should_fail/tcfail212.stderr   |   24 +-
 testsuite/tests/typecheck/should_fail/tcfail213.hs |    2 +-
 testsuite/tests/typecheck/should_fail/tcfail214.hs |    2 +-
 .../tests/typecheck/should_fail/tcfail217.stderr   |    2 +-
 testsuite/tests/typecheck/should_run/T10284.hs     |   11 +-
 testsuite/tests/typecheck/should_run/T10284.stderr |    8 +-
 testsuite/tests/typecheck/should_run/T10284.stdout |    2 +-
 testsuite/tests/typecheck/should_run/T7861.stdout  |    1 -
 testsuite/tests/typecheck/should_run/tcrun043.hs   |    2 +-
 testsuite/tests/typecheck/should_run/tcrun044.hs   |    2 +-
 .../tests/warnings/should_compile/T11077.stderr    |    2 +-
 utils/genprimopcode/Main.hs                        |    2 +-
 utils/haddock                                      |    2 +-
 576 files changed, 21781 insertions(+), 15223 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 6746549772c5cc0ac66c0fce562f297f4d4b80a2


More information about the ghc-commits mailing list