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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/41e9276f2574124a6be8b080966a5c86ca2d5df5

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

commit 41e9276f2574124a6be8b080966a5c86ca2d5df5
Merge: 4737d64... 851e4e7...
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Wed Jan 9 09:37:12 2013 +0000

    Merge branch 'master' of http://darcs.haskell.org/ghc
    
    Conflicts:
        compiler/typecheck/FamInst.lhs

 compiler/typecheck/FamInst.lhs |    4 ++--
 1 files changed, 2 insertions(+), 2 deletions(-)

diff --cc compiler/typecheck/FamInst.lhs
index a32df6b,4e47a2d..f667cd5
--- a/compiler/typecheck/FamInst.lhs
+++ b/compiler/typecheck/FamInst.lhs
@@@ -321,22 -321,22 +321,22 @@@ conflictInstErr fam_inst branch conflic
                    , fim_index = confIndex }) : _ <- conflictingMatch
    = addFamInstsErr (ptext (sLit "Conflicting family instance declarations:"))
                     [(fam_inst, branch),
 -                    (confInst, famInstNthBranch confInst confIndex)]
 +                    (confInst, confIndex) ]
-   | otherwise
-   = pprPanic "conflictInstErr" (pprCoAxBranchHdr (famInstAxiom fam_inst) 
branch)
+   | otherwise -- no conflict on this branch; see Trac #7560
+   = return ()
  
 -addFamInstsErr :: SDoc -> [(FamInst Branched, FamInstBranch)] -> TcRn ()
 +addFamInstsErr :: SDoc -> [(FamInst Branched, Int)] -> TcRn ()
  addFamInstsErr herald insts
 -  = setSrcSpan srcSpan $
 -    addErr (hang herald 2 $ vcat (zipWith pprFamInstBranchHdr
 -                                          sortedAxioms sortedBranches))
 +  = ASSERT( not (null insts) )
 +    setSrcSpan srcSpan $ addErr $
 +    hang herald
 +       2 (vcat [ pprCoAxBranchHdr (famInstAxiom fi) index 
 +               | (fi,index) <- sorted ])
   where
 -   getSpan = famInstBranchSpan . snd
 -   sorted = sortWith getSpan insts
 -   srcSpan = getSpan $ head sorted
 -
 -   sortedAxioms = map (famInstAxiom . fst) sorted
 -   sortedBranches = map snd sorted
 +   getSpan   = getSrcLoc . famInstAxiom . fst
 +   sorted    = sortWith getSpan insts
 +   (fi1,ix1) = head sorted
 +   srcSpan   = coAxBranchSpan (coAxiomNthBranch (famInstAxiom fi1) ix1)
     -- The sortWith just arranges that instances are dislayed in order
     -- of source location, which reduced wobbling in error messages,
     -- and is better for users



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

Reply via email to