[commit: ghc] master: Remove unused field in ConDecl (ea8c116)

git at git.haskell.org git at git.haskell.org
Wed Nov 11 11:02:27 UTC 2015


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

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

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

commit ea8c116ac9eb916fdb6360a01c285bc8698dfaf9
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Wed Nov 11 11:34:48 2015 +0100

    Remove unused field in ConDecl
    
    We no longer parse old-style GADT syntax but there was some left-over
    code for emitting deprecation warnings.
    
    Updates haddock submodule.
    
    Test Plan: ./validate
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1460


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

ea8c116ac9eb916fdb6360a01c285bc8698dfaf9
 compiler/hsSyn/HsDecls.hs   |  6 ------
 compiler/parser/RdrHsSyn.hs |  6 ++----
 compiler/rename/RnSource.hs | 10 +---------
 utils/haddock               |  2 +-
 4 files changed, 4 insertions(+), 20 deletions(-)

diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs
index 7e01bc3..ec46d0e 100644
--- a/compiler/hsSyn/HsDecls.hs
+++ b/compiler/hsSyn/HsDecls.hs
@@ -1045,12 +1045,6 @@ data ConDecl name
 
     , con_doc       :: Maybe LHsDocString
         -- ^ A possible Haddock comment.
-
-    , con_old_rec :: Bool
-        -- ^ TEMPORARY field; True <=> user has employed now-deprecated syntax for
-        --                             GADT-style record decl   C { blah } :: T a b
-        -- Remove this when we no longer parse this stuff, and hence do not
-        -- need to report decprecated use
     } deriving (Typeable)
 deriving instance (DataId name) => Data (ConDecl name)
 
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index b24ba09..5aa91ec 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -487,8 +487,7 @@ mkSimpleConDecl :: Located RdrName -> [LHsTyVarBndr RdrName]
                 -> ConDecl RdrName
 
 mkSimpleConDecl name qvars cxt details
-  = ConDecl { con_old_rec  = False
-            , con_names    = [name]
+  = ConDecl { con_names    = [name]
             , con_explicit = Explicit
             , con_qvars    = mkHsQTvs qvars
             , con_cxt      = cxt
@@ -523,8 +522,7 @@ mkGadtDecl' names (L ls (HsForAllTy imp _ qvars cxt tau))
           _other                                    -> (PrefixCon [], tau)
 
     mk_gadt_con names
-       = ConDecl { con_old_rec  = False
-                 , con_names    = names
+       = ConDecl { con_names    = names
                  , con_explicit = imp
                  , con_qvars    = qvars
                  , con_cxt      = cxt
diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs
index 4e3359f..0bd96ec 100644
--- a/compiler/rename/RnSource.hs
+++ b/compiler/rename/RnSource.hs
@@ -1444,9 +1444,8 @@ rnConDecl :: ConDecl RdrName -> RnM (ConDecl Name, FreeVars)
 rnConDecl decl@(ConDecl { con_names = names, con_qvars = tvs
                         , con_cxt = lcxt@(L loc cxt), con_details = details
                         , con_res = res_ty, con_doc = mb_doc
-                        , con_old_rec = old_rec, con_explicit = expl })
+                        , con_explicit = expl })
   = do  { mapM_ (addLocM checkConName) names
-        ; when old_rec (addWarn (deprecRecSyntax decl))
         ; new_names <- mapM lookupLocatedTopBndrRn names
 
            -- For H98 syntax, the tvs are the existential ones
@@ -1530,13 +1529,6 @@ rnConDeclDetails con doc (RecCon (L l fields))
         ; return (RecCon (L l new_fields), fvs) }
 
 -------------------------------------------------
-deprecRecSyntax :: ConDecl RdrName -> SDoc
-deprecRecSyntax decl
-  = vcat [ ptext (sLit "Declaration of") <+> quotes (ppr (con_names decl))
-                 <+> ptext (sLit "uses deprecated syntax")
-         , ptext (sLit "Instead, use the form")
-         , nest 2 (ppr decl) ]   -- Pretty printer uses new form
-
 badRecResTy :: SDoc -> SDoc
 badRecResTy doc = ptext (sLit "Malformed constructor signature") $$ doc
 
diff --git a/utils/haddock b/utils/haddock
index 52c963e..83a9e9d 160000
--- a/utils/haddock
+++ b/utils/haddock
@@ -1 +1 @@
-Subproject commit 52c963e0b19783c4ca59cd0e8cfe1366dbfa1624
+Subproject commit 83a9e9d2c7f0debec9d56e8b3b7cc8a8eb73361e



More information about the ghc-commits mailing list