[commit: ghc] wip/pattern-synonyms: Pattern synonyms have no implicit Ids (e51b7fa)

git at git.haskell.org git at git.haskell.org
Tue Apr 29 12:12:44 UTC 2014


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

On branch  : wip/pattern-synonyms
Link       : http://ghc.haskell.org/trac/ghc/changeset/e51b7fa368ff1ea91828aecd473057299e08f718/ghc

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

commit e51b7fa368ff1ea91828aecd473057299e08f718
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Apr 29 13:10:09 2014 +0100

    Pattern synonyms have no implicit Ids


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

e51b7fa368ff1ea91828aecd473057299e08f718
 compiler/iface/IfaceSyn.lhs |    6 ------
 compiler/iface/TcIface.lhs  |    5 ++++-
 compiler/main/HscTypes.lhs  |   20 +++++++++++---------
 3 files changed, 15 insertions(+), 16 deletions(-)

diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs
index 61a2d69..47ce2cd 100644
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@ -58,7 +58,6 @@ import BooleanFormula ( BooleanFormula )
 
 import Control.Monad
 import System.IO.Unsafe
-import Data.Maybe ( isJust )
 
 infixl 3 &&&
 \end{code}
@@ -1003,11 +1002,6 @@ ifaceDeclImplicitBndrs (IfaceClass {ifCtxt = sc_ctxt, ifName = cls_tc_occ,
     dc_occ = mkClassDataConOcc cls_tc_occ
     is_newtype = n_sigs + n_ctxt == 1 -- Sigh
 
-ifaceDeclImplicitBndrs (IfacePatSyn{ ifName = ps_occ, ifPatWrapper = wrapper_name })
-  = [wrap_occ | isJust wrapper_name]
-  where
-    wrap_occ = mkDataConWrapperOcc ps_occ
-
 ifaceDeclImplicitBndrs _ = []
 
 -- -----------------------------------------------------------------------------
diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs
index e8f2a15..df15c03 100644
--- a/compiler/iface/TcIface.lhs
+++ b/compiler/iface/TcIface.lhs
@@ -589,7 +589,10 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name
                               , ifPatArgs = args })
   = do { name <- lookupIfaceTop occ_name
        ; matcher <- tcExt "Matcher" matcher_name
-       ; wrapper <- maybe (return Nothing) (fmap Just . tcExt "Wrapper") wrapper_name
+       ; wrapper <- case wrapper_name of
+                        Nothing -> return Nothing
+                        Just wn -> do { wid <- tcExt "Wrapper" wn
+                                      ; return (Just wid) }
        ; argNames <- mapM (newIfaceName . mkVarOccFS) args
        ; return $ AConLike . PatSynCon $
              buildPatSyn name is_infix matcher wrapper argNames }
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index 6fcf8e2..58d0c58 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -1504,15 +1504,17 @@ implicitTyThings :: TyThing -> [TyThing]
 implicitTyThings (AnId _)       = []
 implicitTyThings (ACoAxiom _cc) = []
 implicitTyThings (ATyCon tc)    = implicitTyConThings tc
-implicitTyThings (AConLike cl)  = case cl of
-    RealDataCon dc ->
-        -- For data cons add the worker and (possibly) wrapper
-        map AnId (dataConImplicitIds dc)
-    PatSynCon ps ->
-        -- For bidirectional pattern synonyms, add the wrapper
-        case patSynWrapper ps of
-            Nothing -> []
-            Just id -> [AnId id]
+implicitTyThings (AConLike cl)  = implicitConLikeThings cl
+
+implicitConLikeThings :: ConLike -> [TyThing]
+implicitConLikeThings (RealDataCon dc)
+  = map AnId (dataConImplicitIds dc)
+    -- For data cons add the worker and (possibly) wrapper
+
+implicitConLikeThings (PatSynCon {})
+  = []  -- Pattern synonyms have no implicit Ids; the wrapper and matcher
+        -- are not "implicit"; they are simply new top-level bindings,
+        -- and they have their own declaration in an interface fiel
 
 implicitClassThings :: Class -> [TyThing]
 implicitClassThings cl



More information about the ghc-commits mailing list