[commit: ghc] master: Revert "Simplify the plumbing for checkValidTyCl" (724690f)

git at git.haskell.org git at git.haskell.org
Fri Dec 27 03:39:36 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/724690f86f9bf92e886a785141c9ef423ddae05e/ghc

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

commit 724690f86f9bf92e886a785141c9ef423ddae05e
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Dec 18 14:58:12 2013 -0500

    Revert "Simplify the plumbing for checkValidTyCl"
    
    This reverts commit 174577912de7a21b8fe01881a28f5aafce02b92e.
    
    This is part of the fix for #8607. Only reverting RdrHsSyn.lhs.
    
    Conflicts:
    
    	compiler/parser/RdrHsSyn.lhs
    	compiler/typecheck/TcTyClsDecls.lhs


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

724690f86f9bf92e886a785141c9ef423ddae05e
 compiler/parser/RdrHsSyn.lhs |   15 ++++-----------
 1 file changed, 4 insertions(+), 11 deletions(-)

diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs
index 79e53b2..79d2d96 100644
--- a/compiler/parser/RdrHsSyn.lhs
+++ b/compiler/parser/RdrHsSyn.lhs
@@ -127,7 +127,7 @@ mkClassDecl loc (L _ (mcxt, tycl_hdr)) fds where_cls
        ; (cls, tparams) <- checkTyClHdr tycl_hdr
        ; tyvars <- checkTyVars (ptext (sLit "class")) whereDots
                                cls tparams      -- Only type vars allowed
-       ; return (L loc (ClassDecl { tcdCtxt = cxt, tcdLName = reLocate loc cls, tcdTyVars = tyvars,
+       ; return (L loc (ClassDecl { tcdCtxt = cxt, tcdLName = cls, tcdTyVars = tyvars,
                                     tcdFDs = unLoc fds, tcdSigs = sigs, tcdMeths = binds,
                                     tcdATs = ats, tcdATDefs = at_defs, tcdDocs  = docs,
                                     tcdFVs = placeHolderNames })) }
@@ -144,7 +144,7 @@ mkTyData loc new_or_data cType (L _ (mcxt, tycl_hdr)) ksig data_cons maybe_deriv
   = do { (tc, tparams) <- checkTyClHdr tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
        ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv
-       ; return (L loc (DataDecl { tcdLName = reLocate loc tc, tcdTyVars = tyvars,
+       ; return (L loc (DataDecl { tcdLName = tc, tcdTyVars = tyvars,
                                    tcdDataDefn = defn,
                                    tcdFVs = placeHolderNames })) }
 
@@ -171,7 +171,7 @@ mkTySynonym :: SrcSpan
 mkTySynonym loc lhs rhs
   = do { (tc, tparams) <- checkTyClHdr lhs
        ; tyvars <- checkTyVars (ptext (sLit "type")) equalsDots tc tparams
-       ; return (L loc (SynDecl { tcdLName = reLocate loc tc, tcdTyVars = tyvars
+       ; return (L loc (SynDecl { tcdLName = tc, tcdTyVars = tyvars
                                 , tcdRhs = rhs, tcdFVs = placeHolderNames })) }
 
 mkTyFamInstEqn :: LHsType RdrName
@@ -213,7 +213,7 @@ mkFamDecl :: SrcSpan
 mkFamDecl loc info lhs ksig
   = do { (tc, tparams) <- checkTyClHdr lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
-       ; return (L loc (FamDecl (FamilyDecl { fdInfo = info, fdLName = reLocate loc tc
+       ; return (L loc (FamDecl (FamilyDecl { fdInfo = info, fdLName = tc
                                             , fdTyVars = tyvars, fdKindSig = ksig }))) }
   where
     equals_or_where = case info of
@@ -221,13 +221,6 @@ mkFamDecl loc info lhs ksig
                         OpenTypeFamily      -> empty
                         ClosedTypeFamily {} -> whereDots
 
-reLocate :: SrcSpan -> Located a -> Located a
--- For the main binder of a declaration, we make its SrcSpan to
--- cover the whole declaration, rather than just the syntactic occurrence
--- of the binder. This makes error messages refer to the declaration as
--- a whole, rather than just the binding site
-reLocate loc (L _ x) = L loc x
-
 mkSpliceDecl :: LHsExpr RdrName -> HsDecl RdrName
 -- If the user wrote
 --      [pads| ... ]   then return a QuasiQuoteD



More information about the ghc-commits mailing list