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

On branch  : overlapping-tyfams

http://hackage.haskell.org/trac/ghc/changeset/7a01613c1fe81fbe954493ceeb39aa1b71575212

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

commit 7a01613c1fe81fbe954493ceeb39aa1b71575212
Merge: 01b5511... c3b6b3f...
Author: Richard Eisenberg <e...@cis.upenn.edu>
Date:   Sun Sep 9 23:23:18 2012 +0200

    Fixing conflicts from merge with master

 compiler/basicTypes/BasicTypes.lhs                 |    2 +-
 compiler/basicTypes/RdrName.lhs                    |   21 +-
 compiler/cmm/CLabel.hs                             |   33 +-
 compiler/cmm/CmmBuildInfoTables.hs                 |    9 +-
 compiler/cmm/CmmLayoutStack.hs                     |    6 +-
 compiler/cmm/CmmMachOp.hs                          |    5 +-
 compiler/cmm/CmmNode.hs                            |    9 +-
 compiler/cmm/CmmParse.y                            | 1058 ++++++++++----------
 compiler/cmm/CmmPipeline.hs                        |    3 +-
 compiler/cmm/CmmUtils.hs                           |   26 +-
 compiler/cmm/MkGraph.hs                            |  107 ++-
 compiler/codeGen/CallerSaves.hs                    |   51 -
 compiler/codeGen/CgClosure.lhs                     |    8 +-
 compiler/codeGen/CgForeignCall.hs                  |    2 +-
 compiler/codeGen/CgHeapery.lhs                     |   20 +-
 compiler/codeGen/CgPrimOp.hs                       |   61 +-
 compiler/codeGen/CgProf.hs                         |    6 +-
 compiler/codeGen/CgTicky.hs                        |    4 +-
 compiler/codeGen/CgUtils.hs                        |  159 +---
 compiler/codeGen/ClosureInfo.lhs                   |    2 +-
 compiler/codeGen/CodeGen.lhs                       |    3 +-
 compiler/codeGen/CodeGen/Platform.hs               |  111 ++
 compiler/codeGen/CodeGen/Platform/ARM.hs           |    7 +
 compiler/codeGen/CodeGen/Platform/NoRegs.hs        |    6 +
 compiler/codeGen/CodeGen/Platform/PPC.hs           |    7 +
 compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs    |    8 +
 compiler/codeGen/CodeGen/Platform/SPARC.hs         |    7 +
 compiler/codeGen/CodeGen/Platform/X86.hs           |    7 +
 compiler/codeGen/CodeGen/Platform/X86_64.hs        |    7 +
 compiler/codeGen/StgCmm.hs                         |   98 +-
 compiler/codeGen/StgCmmBind.hs                     |  243 +++---
 compiler/codeGen/StgCmmClosure.hs                  |    2 +-
 compiler/codeGen/StgCmmEnv.hs                      |    8 +-
 compiler/codeGen/StgCmmExpr.hs                     |  184 ++--
 compiler/codeGen/StgCmmForeign.hs                  |    2 +-
 compiler/codeGen/StgCmmHeap.hs                     |    2 +-
 compiler/codeGen/StgCmmHpc.hs                      |   15 +-
 compiler/codeGen/StgCmmMonad.hs                    |   25 +-
 compiler/codeGen/StgCmmPrim.hs                     |   89 +-
 compiler/codeGen/StgCmmProf.hs                     |    6 +-
 compiler/codeGen/StgCmmTicky.hs                    |    8 +-
 compiler/codeGen/StgCmmUtils.hs                    |  389 ++++----
 compiler/coreSyn/CorePrep.lhs                      |   46 +-
 compiler/coreSyn/CoreSyn.lhs                       |   21 +
 compiler/coreSyn/CoreUtils.lhs                     |   10 +-
 compiler/coreSyn/MkCore.lhs                        |    6 +-
 compiler/coreSyn/TrieMap.lhs                       |  111 ++-
 compiler/deSugar/Coverage.lhs                      |   94 ++-
 compiler/deSugar/Desugar.lhs                       |    5 +-
 compiler/deSugar/DsBinds.lhs                       |   11 +-
 compiler/deSugar/DsMeta.hs                         |  253 +++--
 compiler/ghc.cabal.in                              |   12 +-
 compiler/ghc.mk                                    |   12 -
 compiler/ghci/Linker.lhs                           |   72 +-
 compiler/hsSyn/Convert.lhs                         |   92 ++-
 compiler/hsSyn/HsDecls.lhs                         |    5 +-
 compiler/iface/IfaceSyn.lhs                        |   22 +
 compiler/iface/MkIface.lhs                         |   24 +-
 compiler/llvmGen/LlvmCodeGen.hs                    |    2 +-
 compiler/llvmGen/LlvmCodeGen/Base.hs               |   19 +-
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs            |   26 +-
 compiler/llvmGen/LlvmCodeGen/Ppr.hs                |   59 +-
 compiler/main/CmdLineParser.hs                     |   12 +-
 compiler/main/DriverPhases.hs                      |   41 +-
 compiler/main/DriverPipeline.hs                    |   56 +-
 compiler/main/DynFlags.hs                          |  284 +++++-
 compiler/main/GHC.hs                               |    6 +
 compiler/main/HscMain.hs                           |   42 +-
 compiler/main/HscTypes.lhs                         |   37 +-
 compiler/main/Packages.lhs                         |   15 +-
 compiler/main/StaticFlagParser.hs                  |   47 +-
 compiler/main/StaticFlags.hs                       |  249 +-----
 compiler/main/TidyPgm.lhs                          |   26 +-
 compiler/nativeGen/AsmCodeGen.lhs                  |   16 +-
 compiler/nativeGen/Instruction.hs                  |    3 +-
 compiler/nativeGen/PIC.hs                          |   49 +-
 compiler/nativeGen/PPC/CodeGen.hs                  |   52 +-
 compiler/nativeGen/PPC/Instr.hs                    |   25 +-
 compiler/nativeGen/PPC/Ppr.hs                      |   37 +-
 compiler/nativeGen/PPC/Regs.hs                     |  513 ++--------
 compiler/nativeGen/RegAlloc/Graph/Main.hs          |    6 +-
 compiler/nativeGen/RegAlloc/Graph/Spill.hs         |   31 +-
 compiler/nativeGen/RegAlloc/Graph/SpillClean.hs    |    2 +-
 compiler/nativeGen/RegAlloc/Graph/SpillCost.hs     |    8 +-
 compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs     |   20 +-
 .../nativeGen/RegAlloc/Linear/JoinToTargets.hs     |    2 +-
 compiler/nativeGen/RegAlloc/Linear/Main.hs         |   58 +-
 compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs |    5 +-
 .../nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs    |   25 +-
 compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs |   40 +-
 compiler/nativeGen/RegAlloc/Liveness.hs            |   83 +-
 compiler/nativeGen/SPARC/CodeGen.hs                |   10 +-
 compiler/nativeGen/SPARC/CodeGen/Base.hs           |   11 +-
 compiler/nativeGen/SPARC/CodeGen/Gen32.hs          |    7 +-
 compiler/nativeGen/SPARC/Imm.hs                    |    4 +-
 compiler/nativeGen/SPARC/Instr.hs                  |   17 +-
 compiler/nativeGen/SPARC/Ppr.hs                    |   37 +-
 compiler/nativeGen/SPARC/RegPlate.hs               |  318 ------
 compiler/nativeGen/SPARC/Regs.hs                   |  130 +---
 compiler/nativeGen/TargetReg.hs                    |   10 +-
 compiler/nativeGen/X86/CodeGen.hs                  |  173 ++--
 compiler/nativeGen/X86/Instr.hs                    |   32 +-
 compiler/nativeGen/X86/Regs.hs                     |  375 ++------
 compiler/parser/Lexer.x                            |    7 +-
 compiler/parser/Parser.y.pp                        |   24 +-
 compiler/prelude/primops.txt.pp                    |    2 +-
 compiler/rename/RnEnv.lhs                          |   31 +-
 compiler/rename/RnNames.lhs                        |  210 +++--
 compiler/rename/RnTypes.lhs                        |   26 +-
 compiler/simplCore/CoreMonad.lhs                   |   14 +-
 compiler/simplCore/SimplMonad.lhs                  |    6 +-
 compiler/specialise/Rules.lhs                      |    7 +-
 compiler/specialise/SpecConstr.lhs                 |    6 +-
 compiler/specialise/Specialise.lhs                 |   12 +-
 compiler/stgSyn/StgSyn.lhs                         |    4 +-
 compiler/typecheck/TcBinds.lhs                     |   57 +-
 compiler/typecheck/TcCanonical.lhs                 |   12 +-
 compiler/typecheck/TcEvidence.lhs                  |   44 +-
 compiler/typecheck/TcHsSyn.lhs                     |    2 +-
 compiler/typecheck/TcHsType.lhs                    |   18 +-
 compiler/typecheck/TcInstDcls.lhs                  |    4 +-
 compiler/typecheck/TcMType.lhs                     |   44 +-
 compiler/typecheck/TcPat.lhs                       |   10 +-
 compiler/typecheck/TcRnTypes.lhs                   |    2 +-
 compiler/typecheck/TcSimplify.lhs                  |   84 +--
 compiler/typecheck/TcTyClsDecls.lhs                |   26 +-
 compiler/utils/Util.lhs                            |   17 +-
 docs/users_guide/flags.xml                         |    4 +-
 docs/users_guide/ghci.xml                          |   43 +-
 docs/users_guide/glasgow_exts.xml                  |  148 ++-
 docs/users_guide/using.xml                         |   19 +-
 ghc/InteractiveUI.hs                               |   66 +-
 ghc/Main.hs                                        |   33 +-
 ghc/ghc-bin.cabal.in                               |    2 +-
 ghc/ghc.mk                                         |    4 +-
 ghc/hschooks.c                                     |   10 +-
 includes/CallerSaves.part.hs                       |   81 --
 includes/CodeGen.Platform.hs                       |  735 ++++++++++++++
 includes/mkDerivedConstants.c                      |    2 +-
 includes/rts/Hooks.h                               |    6 +-
 includes/rts/SpinLock.h                            |    2 +-
 includes/rts/Threads.h                             |    8 +-
 includes/rts/Types.h                               |    6 +-
 includes/rts/prof/CCS.h                            |    9 +
 includes/rts/storage/Block.h                       |    4 +-
 includes/rts/storage/ClosureMacros.h               |   68 +-
 includes/rts/storage/GC.h                          |   12 +-
 includes/rts/storage/MBlock.h                      |    6 +-
 includes/stg/Types.h                               |   18 +-
 mk/config.mk.in                                    |   12 +-
 rts/Arena.c                                        |    2 +-
 rts/Capability.h                                   |    2 +-
 rts/Disassembler.c                                 |    2 +-
 rts/FrontPanel.c                                   |    2 +-
 rts/FrontPanel.h                                   |    2 +-
 rts/Interpreter.c                                  |    2 +-
 rts/Linker.c                                       |   78 ++-
 rts/Messages.c                                     |   10 +-
 rts/Printer.c                                      |   29 +-
 rts/ProfHeap.c                                     |    2 +-
 rts/Profiling.c                                    |    5 +-
 rts/Proftimer.c                                    |    8 +-
 rts/Proftimer.h                                    |    5 -
 rts/RaiseAsync.c                                   |    2 +-
 rts/RetainerProfile.c                              |    4 +-
 rts/RetainerProfile.h                              |    2 +-
 rts/RtsAPI.c                                       |    6 +-
 rts/RtsFlags.c                                     |    2 +-
 rts/RtsUtils.c                                     |    2 +-
 rts/Schedule.c                                     |   21 +-
 rts/Stats.c                                        |   34 +-
 rts/Stats.h                                        |    4 +-
 rts/Threads.c                                      |   16 +-
 rts/Threads.h                                      |    2 +-
 rts/Trace.c                                        |   46 +-
 rts/Trace.h                                        |   44 +-
 rts/eventlog/EventLog.c                            |   20 +-
 rts/eventlog/EventLog.h                            |   20 +-
 rts/hooks/MallocFail.c                             |    2 +-
 rts/hooks/OutOfHeap.c                              |    2 +-
 rts/hooks/StackOverflow.c                          |    2 +-
 rts/parallel/ParTicky.c                            |    4 +-
 rts/posix/OSMem.c                                  |   12 +-
 rts/posix/OSThreads.c                              |    6 +-
 rts/sm/BlockAlloc.c                                |   85 ++-
 rts/sm/BlockAlloc.h                                |   12 +-
 rts/sm/Compact.c                                   |   22 +-
 rts/sm/Evac.c                                      |    6 +-
 rts/sm/Evac.h                                      |    2 +-
 rts/sm/GC.c                                        |   98 +--
 rts/sm/GCThread.h                                  |   18 +-
 rts/sm/GCUtils.c                                   |    2 +-
 rts/sm/MBlock.c                                    |    6 +-
 rts/sm/MarkWeak.c                                  |   23 +-
 rts/sm/OSMem.h                                     |    4 +-
 rts/sm/Sanity.c                                    |   34 +-
 rts/sm/Scav.c                                      |    8 +-
 rts/sm/Storage.c                                   |  125 ++-
 rts/sm/Storage.h                                   |   30 +-
 rts/sm/Sweep.c                                     |    2 +-
 rts/win32/OSMem.c                                  |   30 +-
 rules/haddock.mk                                   |    3 +-
 utils/ghc-cabal/Main.hs                            |    3 +-
 utils/ghc-cabal/ghc-cabal.cabal                    |    3 +-
 utils/ghc-pkg/ghc-pkg.cabal                        |    2 +-
 utils/ghc-pkg/ghc.mk                               |    4 +-
 utils/ghc-pwd/ghc-pwd.cabal                        |    2 +-
 utils/hpc/hpc-bin.cabal                            |    2 +-
 utils/runghc/runghc.cabal.in                       |    2 +-
 209 files changed, 4957 insertions(+), 4582 deletions(-)

diff --cc compiler/iface/IfaceSyn.lhs
index 7f1e52e,a41a9da..a6e9e8e
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@@ -24,9 -24,10 +24,10 @@@ module IfaceSyn 
  
          -- Misc
          ifaceDeclImplicitBndrs, visibleIfConDecls,
+         ifaceDeclFingerprints,
  
          -- Free Names
 -        freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
 +        freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInstGroup,
  
          -- Pretty printing
          pprIfaceExpr, pprIfaceDeclHead
diff --cc compiler/typecheck/TcInstDcls.lhs
index cd75239,140e1c8..c749d54
--- a/compiler/typecheck/TcInstDcls.lhs
+++ b/compiler/typecheck/TcInstDcls.lhs
@@@ -428,13 -427,13 +428,13 @@@ addClsInsts :: [InstInfo Name] -> TcM 
  addClsInsts infos thing_inside
    = tcExtendLocalInstEnv (map iSpec infos) thing_inside
  
 -addFamInsts :: [FamInst] -> TcM a -> TcM a
 +addFamInstGroups :: [FamInstGroup] -> TcM a -> TcM a
  -- Extend (a) the family instance envt
  --        (b) the type envt with stuff from data type decls
 -addFamInsts fam_insts thing_inside
 -  = tcExtendLocalFamInstEnv fam_insts $ 
 -    tcExtendGlobalEnv things $
 -    do { traceTc "addFamInsts" (pprFamInsts fam_insts)
 +addFamInstGroups fam_inst_grps thing_inside
 +  = tcExtendLocalFamInstEnv fam_inst_grps $ 
-     tcExtendGlobalEnvImplicit things  $ 
++    tcExtendGlobalEnv things  $ 
 +    do { traceTc "addFamInsts" (pprFamInstGroups fam_inst_grps)
         ; tcg_env <- tcAddImplicits things
         ; setGblEnv tcg_env thing_inside }
    where
diff --cc compiler/typecheck/TcTyClsDecls.lhs
index 026e10a,743bd7c..c875e9b
--- a/compiler/typecheck/TcTyClsDecls.lhs
+++ b/compiler/typecheck/TcTyClsDecls.lhs
@@@ -149,10 -147,12 +149,11 @@@ tcTyClGroup boot_details tycld
             -- expects well-formed TyCons
         ; tcExtendGlobalEnv tyclss $ do
         { traceTc "Starting validity check" (ppr tyclss)
-        ; mapM_ (recoverM (return ()) . addLocM checkValidTyCl) tyclds
+        ; checkNoErrs $
 -         mapM_ (recoverM (return ()) . addLocM checkValidTyCl) 
 -               (flattenTyClDecls tyclds)
++         mapM_ (recoverM (return ()) . addLocM checkValidTyCl) tyclds
             -- We recover, which allows us to report multiple validity errors
-            -- even from successive groups.  But we stop after all groups are
-            -- processed if we find any errors.
+            -- but we then fail if any are wrong.  Lacking the checkNoErrs
+            -- we get Trac #7175
  
             -- Step 4: Add the implicit things;
             -- we want them in the environment because



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

Reply via email to