[commit: ghc] master: Comments in TH.Syntax (Trac #12596) (a72d798)

git at git.haskell.org git at git.haskell.org
Thu Sep 15 16:24:11 UTC 2016


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

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

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

commit a72d798ce948b054f47d7acd72799384cf06deea
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Sep 14 08:38:33 2016 +0100

    Comments in TH.Syntax (Trac #12596)
    
    See Note [Data for non-algebraic types]


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

a72d798ce948b054f47d7acd72799384cf06deea
 .../template-haskell/Language/Haskell/TH/Syntax.hs | 37 ++++++++++++++++++----
 1 file changed, 31 insertions(+), 6 deletions(-)

diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index 1129239..20c2396 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -716,15 +716,12 @@ dataToQa mkCon mkLit appCon antiQ t =
                                           (NameG DataName
                                                 (mkPkgName "ghc-prim")
                                                 (mkModName "GHC.Tuple"))
-                      -- It is possible for a Data instance to be defined such
-                      -- that toConstr uses a Constr defined using a function,
-                      -- not a data constructor. In such a case, we must take
-                      -- care to build the Name using mkNameG_v (for values),
-                      -- not mkNameG_d (for data constructors).
-                      -- See Trac #10796.
+
+                      -- Tricky case: see Note [Data for non-algebraic types]
                       fun@(x:_)   | startsVarSym x || startsVarId x
                                   -> mkNameG_v tyconPkg tyconMod fun
                       con         -> mkNameG_d tyconPkg tyconMod con
+
                   where
                     tycon :: TyCon
                     tycon = (typeRepTyCon . typeOf) t
@@ -747,6 +744,34 @@ dataToQa mkCon mkLit appCon antiQ t =
 
       Just y -> y
 
+
+{- Note [Data for non-algebraic types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Class Data was originally intended for algebraic data types.  But
+it is possible to use it for abstract types too.  For example, in
+package `text` we find
+
+  instance Data Text where
+    ...
+    toConstr _ = packConstr
+
+  packConstr :: Constr
+  packConstr = mkConstr textDataType "pack" [] Prefix
+
+Here `packConstr` isn't a real data constructor, it's an ordiary
+function.  Two complications
+
+* In such a case, we must take care to build the Name using
+  mkNameG_v (for values), not mkNameG_d (for data constructors).
+  See Trac #10796.
+
+* The pseudo-constructor is named only by its string, here "pack".
+  But 'dataToQa' needs the TyCon of its defining module, and has
+  to assume it's defined in the same module as the TyCon itself.
+  But nothing enforces that; Trac #12596 shows what goes wrong if
+  "pack" is defined in a different module than the data type "Text".
+  -}
+
 -- | 'dataToExpQ' converts a value to a 'Q Exp' representation of the
 -- same value, in the SYB style. It is generalized to take a function
 -- override type-specific cases; see 'liftData' for a more commonly



More information about the ghc-commits mailing list