[commit: ghc] master: Use a new $b prefix for pattern synonym builder names, instead of re-using $W from wrappers (5326348)

git at git.haskell.org git at git.haskell.org
Sat Dec 20 13:36:42 UTC 2014


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

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

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

commit 5326348076b9ba091b5af8f5dababdb2a9ea1977
Author: Dr. ERDI Gergo <gergo at erdi.hu>
Date:   Sat Dec 20 21:34:08 2014 +0800

    Use a new $b prefix for pattern synonym builder names, instead of re-using $W from wrappers


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

5326348076b9ba091b5af8f5dababdb2a9ea1977
 compiler/basicTypes/OccName.hs |  9 +++++++--
 compiler/basicTypes/PatSyn.hs  | 12 ++++++------
 compiler/typecheck/TcPatSyn.hs |  2 +-
 3 files changed, 14 insertions(+), 9 deletions(-)

diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs
index b7da021..0c23ddc 100644
--- a/compiler/basicTypes/OccName.hs
+++ b/compiler/basicTypes/OccName.hs
@@ -53,7 +53,9 @@ module OccName (
 
         -- ** Derived 'OccName's
         isDerivedOccName,
-        mkDataConWrapperOcc, mkWorkerOcc, mkMatcherOcc, mkDefaultMethodOcc,
+        mkDataConWrapperOcc, mkWorkerOcc,
+        mkMatcherOcc, mkBuilderOcc,
+        mkDefaultMethodOcc,
         mkGenDefMethodOcc,
         mkDerivedTyConOcc, mkNewTyCoOcc, mkClassOpAuxOcc,
         mkCon2TagOcc, mkTag2ConOcc, mkMaxTagOcc,
@@ -595,7 +597,9 @@ isDerivedOccName occ =
      ':':c:_ | isAlphaNum c -> True
      _other                 -> False
 
-mkDataConWrapperOcc, mkWorkerOcc, mkMatcherOcc, mkDefaultMethodOcc,
+mkDataConWrapperOcc, mkWorkerOcc,
+        mkMatcherOcc, mkBuilderOcc,
+        mkDefaultMethodOcc,
         mkGenDefMethodOcc, mkDerivedTyConOcc, mkClassDataConOcc, mkDictOcc,
         mkIPOcc, mkSpecOcc, mkForeignExportOcc, mkRepEqOcc, mkGenOcc1, mkGenOcc2,
         mkGenD, mkGenR, mkGen1R, mkGenRCo,
@@ -608,6 +612,7 @@ mkDataConWrapperOcc, mkWorkerOcc, mkMatcherOcc, mkDefaultMethodOcc,
 mkDataConWrapperOcc = mk_simple_deriv varName  "$W"
 mkWorkerOcc         = mk_simple_deriv varName  "$w"
 mkMatcherOcc        = mk_simple_deriv varName  "$m"
+mkBuilderOcc        = mk_simple_deriv varName  "$b"
 mkDefaultMethodOcc  = mk_simple_deriv varName  "$dm"
 mkGenDefMethodOcc   = mk_simple_deriv varName  "$gdm"
 mkClassOpAuxOcc     = mk_simple_deriv varName  "$c"
diff --git a/compiler/basicTypes/PatSyn.hs b/compiler/basicTypes/PatSyn.hs
index f2cef7b..081968a 100644
--- a/compiler/basicTypes/PatSyn.hs
+++ b/compiler/basicTypes/PatSyn.hs
@@ -83,7 +83,7 @@ data PatSyn
         psBuilder     :: Maybe (Id, Bool)
              -- Nothing  => uni-directional pattern synonym
              -- Just (builder, is_unlifted) => bi-directional
-             -- Wrapper function, of type
+             -- Builder function, of type
              --  forall univ_tvs, ex_tvs. (prov_theta, req_theta)
              --                       =>  arg_tys -> res_ty
              -- See Note [Builder for pattern synonyms with unboxed type]
@@ -161,12 +161,12 @@ For *bidirectional* pattern synonyms, we also generate a "builder"
 function which implements the pattern synonym in an expression
 context. For our running example, it will be:
 
-        $WP :: forall t b. (Show (Maybe t), Ord b, Eq t, Num t)
+        $bP :: forall t b. (Show (Maybe t), Ord b, Eq t, Num t)
             => b -> T (Maybe t)
-        $WP x = MkT [x] (Just 42)
+        $bP x = MkT [x] (Just 42)
 
 NB: the existential/universal and required/provided split does not
-apply to the wrapper since you are only putting stuff in, not getting
+apply to the builder since you are only putting stuff in, not getting
 stuff out.
 
 Injectivity of bidirectional pattern synonyms is checked in
@@ -181,8 +181,8 @@ would be a top-level declaration with an unboxed type.
 
         pattern P = 0#
 
-        $WP :: Void# -> Int#
-        $WP _ = 0#
+        $bP :: Void# -> Int#
+        $bP _ = 0#
 
 This means that when typechecking an occurrence of P in an expression,
 we must remember that the builder has this void argument. This is
diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs
index 4c49fb6..9287757 100644
--- a/compiler/typecheck/TcPatSyn.hs
+++ b/compiler/typecheck/TcPatSyn.hs
@@ -326,7 +326,7 @@ mkPatSynBuilderId dir  (L _ name) qtvs theta arg_tys pat_ty
   | isUnidirectional dir
   = return Nothing
   | otherwise
-  = do { builder_name <- newImplicitBinder name mkDataConWorkerOcc
+  = do { builder_name <- newImplicitBinder name mkBuilderOcc
        ; let builder_sigma = mkSigmaTy qtvs theta (mkFunTys builder_arg_tys pat_ty)
              builder_id    = mkExportedLocalId VanillaId builder_name builder_sigma
                              -- See Note [Exported LocalIds] in Id



More information about the ghc-commits mailing list