Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : type-nats

http://hackage.haskell.org/trac/ghc/changeset/b6ef3529236dcd24a6aa38f80605294a05defc13

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

commit b6ef3529236dcd24a6aa38f80605294a05defc13
Merge: fb80c00... 1b02de8...
Author: Iavor S. Diatchki <diatchki@Perun.(none)>
Date:   Sun Oct 28 15:50:31 2012 -0700

    Merge remote-tracking branch 'origin/master' into type-nats

 .gitignore                                         |   43 -
 aclocal.m4                                         |    2 +-
 compiler/basicTypes/DataCon.lhs                    |   69 +-
 compiler/basicTypes/Name.lhs                       |    6 +-
 compiler/basicTypes/OccName.lhs                    |   57 +-
 compiler/basicTypes/Var.lhs                        |    2 +-
 compiler/cmm/CLabel.hs                             |    8 +-
 compiler/cmm/CmmInfo.hs                            |    2 +-
 compiler/cmm/CmmOpt.hs                             |   14 +
 compiler/cmm/CmmParse.y                            |    4 +-
 compiler/cmm/CmmPipeline.hs                        |   44 +-
 compiler/cmm/CmmProcPoint.hs                       |   43 +-
 compiler/cmm/CmmSink.hs                            |   76 +-
 compiler/cmm/CmmUtils.hs                           |    2 +
 compiler/cmm/OldCmm.hs                             |    5 +-
 compiler/cmm/PprC.hs                               |    2 +-
 compiler/cmm/SMRep.lhs                             |    5 +-
 compiler/codeGen/CgBindery.lhs                     |  564 ----------
 compiler/codeGen/CgBindery.lhs-boot                |   11 -
 compiler/codeGen/CgCallConv.hs                     |  414 -------
 compiler/codeGen/CgCase.lhs                        |  673 -----------
 compiler/codeGen/CgClosure.lhs                     |  641 -----------
 compiler/codeGen/CgCon.lhs                         |  490 --------
 compiler/codeGen/CgExpr.lhs                        |  496 --------
 compiler/codeGen/CgExpr.lhs-boot                   |    7 -
 compiler/codeGen/CgForeignCall.hs                  |  322 ------
 compiler/codeGen/CgHeapery.lhs                     |  642 -----------
 compiler/codeGen/CgHpc.hs                          |   40 -
 compiler/codeGen/CgInfoTbls.hs                     |  374 -------
 compiler/codeGen/CgLetNoEscape.lhs                 |  215 ----
 compiler/codeGen/CgMonad.lhs                       |  849 --------------
 compiler/codeGen/CgParallel.hs                     |  100 --
 compiler/codeGen/CgPrimOp.hs                       | 1177 --------------------
 compiler/codeGen/CgProf.hs                         |  310 -----
 compiler/codeGen/CgStackery.lhs                    |  371 ------
 compiler/codeGen/CgTailCall.lhs                    |  509 ---------
 compiler/codeGen/CgTicky.hs                        |  397 -------
 compiler/codeGen/CgUtils.hs                        |  756 +-------------
 compiler/codeGen/ClosureInfo.lhs                   | 1122 -------------------
 compiler/codeGen/ClosureInfo.lhs-boot              |    6 -
 compiler/codeGen/StgCmm.hs                         |    2 +-
 compiler/codeGen/StgCmmBind.hs                     |   10 +-
 compiler/codeGen/StgCmmClosure.hs                  |   10 +-
 compiler/codeGen/StgCmmCon.hs                      |    4 +-
 compiler/codeGen/StgCmmForeign.hs                  |    4 +-
 compiler/codeGen/StgCmmGran.hs                     |    2 +-
 compiler/codeGen/StgCmmHeap.hs                     |    2 +-
 compiler/codeGen/StgCmmHpc.hs                      |    2 +-
 compiler/codeGen/StgCmmLayout.hs                   |   24 +-
 compiler/codeGen/StgCmmPrim.hs                     |    2 +-
 compiler/codeGen/StgCmmProf.hs                     |   10 +-
 compiler/codeGen/StgCmmTicky.hs                    |    2 +-
 compiler/coreSyn/CoreArity.lhs                     |    6 +-
 compiler/coreSyn/CoreLint.lhs                      |    3 +-
 compiler/coreSyn/CoreSubst.lhs                     |    2 +-
 compiler/coreSyn/CoreUtils.lhs                     |   40 +-
 compiler/coreSyn/MkExternalCore.lhs                |    2 +-
 compiler/coreSyn/PprCore.lhs                       |   14 +-
 compiler/deSugar/Coverage.lhs                      |   14 +-
 compiler/deSugar/Desugar.lhs                       |    8 +-
 compiler/deSugar/DsExpr.lhs                        |    6 +-
 compiler/deSugar/DsListComp.lhs                    |    2 +-
 compiler/deSugar/DsMeta.hs                         |  132 ++--
 compiler/deSugar/DsMonad.lhs                       |    4 +-
 compiler/deSugar/Match.lhs                         |    3 +-
 compiler/ghc.cabal.in                              |   22 +-
 compiler/ghci/ByteCodeAsm.lhs                      |   32 +-
 compiler/ghci/ByteCodeGen.lhs                      |  129 ++-
 compiler/ghci/ByteCodeInstr.lhs                    |    6 +-
 compiler/ghci/ByteCodeItbls.lhs                    |    7 +-
 compiler/ghci/Debugger.hs                          |    8 +-
 compiler/ghci/DebuggerUtils.hs                     |    2 +-
 compiler/ghci/Linker.lhs                           |   11 +-
 compiler/hsSyn/HsBinds.lhs                         |   16 -
 compiler/hsSyn/HsExpr.lhs                          |  123 +--
 compiler/iface/FlagChecker.hs                      |    2 +-
 compiler/iface/LoadIface.lhs                       |    2 +-
 compiler/iface/MkIface.lhs                         |    2 +-
 compiler/iface/TcIface.lhs                         |    8 +-
 compiler/llvmGen/LlvmCodeGen/Base.hs               |    2 +-
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs            |    4 +-
 compiler/main/CodeOutput.lhs                       |    2 +-
 compiler/main/DriverPipeline.hs                    |   58 +-
 compiler/main/DynFlags.hs                          |  359 ++++---
 compiler/main/ErrUtils.lhs                         |   52 +-
 compiler/main/Finder.lhs                           |    2 +-
 compiler/main/GHC.hs                               |    4 +-
 compiler/main/GhcMake.hs                           |    8 +-
 compiler/main/HeaderInfo.hs                        |    2 +-
 compiler/main/HscMain.hs                           |    4 +-
 compiler/main/HscTypes.lhs                         |    2 +-
 compiler/main/InteractiveEval.hs                   |    8 +-
 compiler/main/Packages.lhs                         |   14 +-
 compiler/main/SysTools.lhs                         |   12 +-
 compiler/main/TidyPgm.lhs                          |    4 +-
 compiler/nativeGen/AsmCodeGen.lhs                  |   12 +-
 compiler/nativeGen/PIC.hs                          |  477 ++++----
 compiler/nativeGen/PPC/CodeGen.hs                  |    4 +-
 compiler/nativeGen/RegAlloc/Graph/Main.hs          |    6 +-
 compiler/nativeGen/SPARC/CodeGen.hs                |    2 +-
 compiler/nativeGen/X86/CodeGen.hs                  |    8 +-
 compiler/parser/Lexer.x                            |   10 +-
 compiler/parser/Parser.y.pp                        |    8 +-
 compiler/prelude/PrelNames.lhs                     |   13 +
 compiler/prelude/PrelRules.lhs                     |  101 ++-
 compiler/prelude/TysWiredIn.lhs                    |    6 +-
 compiler/profiling/ProfInit.hs                     |    2 +-
 compiler/profiling/SCCfinal.lhs                    |    4 +-
 compiler/rename/RnBinds.lhs                        |   51 +-
 compiler/rename/RnEnv.lhs                          |   10 +-
 compiler/rename/RnExpr.lhs                         |    2 +-
 compiler/rename/RnNames.lhs                        |   14 +-
 compiler/rename/RnTypes.lhs                        |    2 +-
 compiler/simplCore/CoreMonad.lhs                   |   16 +-
 compiler/simplCore/FloatOut.lhs                    |    2 +-
 compiler/simplCore/OccurAnal.lhs                   |  335 +++---
 compiler/simplCore/SimplCore.lhs                   |   24 +-
 compiler/simplCore/SimplUtils.lhs                  |   10 +-
 compiler/simplCore/Simplify.lhs                    |    4 +-
 compiler/simplStg/SimplStg.lhs                     |  105 +-
 compiler/stgSyn/StgSyn.lhs                         |    2 +-
 compiler/typecheck/Inst.lhs                        |   30 +-
 compiler/typecheck/TcBinds.lhs                     |    2 +-
 compiler/typecheck/TcCanonical.lhs                 |   78 +--
 compiler/typecheck/TcErrors.lhs                    |   30 +-
 compiler/typecheck/TcExpr.lhs                      |    3 +-
 compiler/typecheck/TcHsType.lhs                    |  155 ++--
 compiler/typecheck/TcInteract.lhs                  |   80 +-
 compiler/typecheck/TcMType.lhs                     |   13 +-
 compiler/typecheck/TcPat.lhs                       |    2 +-
 compiler/typecheck/TcRnDriver.lhs                  |   16 +-
 compiler/typecheck/TcRnMonad.lhs                   |   47 +-
 compiler/typecheck/TcRnTypes.lhs                   |   16 +-
 compiler/typecheck/TcSMonad.lhs                    |    6 +-
 compiler/typecheck/TcSimplify.lhs                  |  293 +++---
 compiler/typecheck/TcSplice.lhs                    |   18 +-
 compiler/typecheck/TcSplice.lhs-boot               |    2 +-
 compiler/typecheck/TcTyClsDecls.lhs                |   38 +-
 compiler/typecheck/TcType.lhs                      |  108 ++-
 compiler/typecheck/TcUnify.lhs                     |  148 ++--
 compiler/types/Kind.lhs                            |    2 +-
 compiler/types/TyCon.lhs                           |    2 +-
 compiler/vectorise/Vectorise/Exp.hs                |    4 +-
 compiler/vectorise/Vectorise/Monad/Base.hs         |    2 +-
 docs/users_guide/flags.xml                         |    6 +-
 docs/users_guide/glasgow_exts.xml                  |   33 +-
 ghc.mk                                             |   45 +-
 ghc/InteractiveUI.hs                               |   20 +-
 ghc/Main.hs                                        |    6 +-
 includes/Cmm.h                                     |   17 +-
 includes/ghc.mk                                    |    5 +-
 includes/mkDerivedConstants.c                      |    4 +-
 includes/stg/MiscClosures.h                        |    8 +-
 includes/stg/RtsMachRegs.h                         |    6 +
 mk/build.mk.sample                                 |    6 +-
 mk/config.mk.in                                    |    3 +
 mk/validate-settings.mk                            |    2 +-
 mk/ways.mk                                         |    8 +-
 rts/Capability.c                                   |    2 +-
 rts/Exception.cmm                                  |    8 +-
 rts/HeapStackCheck.cmm                             |    2 +-
 rts/Linker.c                                       |    4 +-
 rts/PrimOps.cmm                                    |   48 +-
 rts/Profiling.c                                    |    6 +-
 rts/Schedule.c                                     |   35 +-
 rts/StgStartup.cmm                                 |    2 +-
 rts/StgStdThunks.cmm                               |   18 +-
 rts/Trace.c                                        |    5 +
 rts/Updates.cmm                                    |    8 +-
 rts/Updates.h                                      |    4 +-
 rules/build-dependencies.mk                        |    9 -
 rules/build-package-data.mk                        |   10 +
 rules/build-prog.mk                                |    2 +
 rules/haddock.mk                                   |    6 +-
 rules/{trace.mk => library-path.mk}                |   16 +-
 rules/shell-wrapper.mk                             |   47 +-
 utils/ghc-cabal/Main.hs                            |   25 +-
 utils/ghc-cabal/ghc.mk                             |    2 +-
 utils/ghc-pkg/Main.hs                              |   42 +-
 utils/ghc-pwd/ghc.mk                               |    2 +-
 utils/ghctags/Main.hs                              |    2 +-
 utils/mkUserGuidePart/ghc.mk                       |    8 +-
 .../mkUserGuidePart.cabal}                         |    8 +-
 validate                                           |   23 +-
 184 files changed, 2381 insertions(+), 12544 deletions(-)

diff --cc compiler/coreSyn/CoreLint.lhs
index b7bca66,afd7e05..d2d52c4
--- a/compiler/coreSyn/CoreLint.lhs
+++ b/compiler/coreSyn/CoreLint.lhs
@@@ -886,40 -886,10 +886,41 @@@ lintCoercion co@(AxiomInstCo (CoAxiom 
             ; let ktv_kind = Type.substTy subst_l (tyVarKind ktv)
                    -- Using subst_l is ok, because subst_l and subst_r
                    -- must agree on kind equalities
-            ; unless (k `isSubKind` ktv_kind) (bad_ax (ptext (sLit 
"check_ki2")))
+            ; unless (k `isSubKind` ktv_kind) 
+                     (bad_ax (ptext (sLit "check_ki2") <+> vcat [ ppr co, ppr 
k, ppr ktv, ppr ktv_kind ] ))
             ; return (Type.extendTvSubst subst_l ktv t1, 
                       Type.extendTvSubst subst_r ktv t2) } 
 +
 +lintCoercion (TypeNatCo co ts cs)
 +  = do _ks <- mapM lintType ts
 +       eqs <- mapM lintCoercion cs
 +
 +       let (asmps,(l,r)) = co_axr_inst co ts
 +
 +       kL <- lintType l
 +       kR <- lintType r
 +       checkL (eqKind kL kR)
 +          $ err "Kind error in CoAxiomRule" [ppr kL <+> txt "/=" <+> ppr kR]
 +
 +       check asmps eqs
 +       return (kL, l, r)
 +
 +  where
 +  txt = ptext . sLit
 +  eqn (x,y) = ppr x <+> txt "~" <+> ppr y
 +  err m xs  = hang (txt m) 2 $ vcat (txt "Rule:" <+> ppr (getName co) : xs)
 +
 +  check [] [] = return ()
 +  check ((l,r) : as) ((_,t1,t2) : bs) =
 +           do checkL (eqType l t1 && eqType r t2)
 +                $ err "Mismatch in assumption"
 +                      [ txt "Proof needed:" <+> eqn (l,r)
 +                      , txt "Proof given:"  <+> eqn (t1,t2)
 +                      ]
 +              check as bs
 +  check [] _  = failWithL $ err "Too many proofs" []
 +  check _ []  = failWithL $ err "Not enough proofs" []
 +
  \end{code}
  
  %************************************************************************



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to