[commit: packages/template-haskell] master: Make TExp's argument have nominal role (Trac #8459) (46f8016)

git at git.haskell.org git at git.haskell.org
Tue Oct 22 08:48:12 UTC 2013


Repository : ssh://git@git.haskell.org/template-haskell

On branch  : master
Link       : http://git.haskell.org/packages/template-haskell.git/commitdiff/46f8016024d3b5bf427848543d57fe45a946d971

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

commit 46f8016024d3b5bf427848543d57fe45a946d971
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Oct 22 09:47:52 2013 +0100

    Make TExp's argument have nominal role (Trac #8459)


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

46f8016024d3b5bf427848543d57fe45a946d971
 Language/Haskell/TH/Syntax.hs |   16 +++++++++++++++-
 1 file changed, 15 insertions(+), 1 deletion(-)

diff --git a/Language/Haskell/TH/Syntax.hs b/Language/Haskell/TH/Syntax.hs
index 9660dcd..c4f4435 100644
--- a/Language/Haskell/TH/Syntax.hs
+++ b/Language/Haskell/TH/Syntax.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnboxedTuples, RoleAnnotations #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -156,6 +156,7 @@ instance Applicative Q where
 --
 -----------------------------------------------------
 
+type role TExp nominal   -- See Note [Role of TExp]
 newtype TExp a = TExp { unType :: Exp }
 
 unTypeQ :: Q (TExp a) -> Q Exp
@@ -166,6 +167,19 @@ unsafeTExpCoerce :: Q Exp -> Q (TExp a)
 unsafeTExpCoerce m = do { e <- m
                         ; return (TExp e) }
 
+{- Note [Role of TExp]
+~~~~~~~~~~~~~~~~~~~~~~
+TExp's argument must have a nominal role, not phantom as would
+be inferred (Trac #8459).  Consider
+
+  e :: TExp Age
+  e = MkAge 3
+
+  foo = $(coerce e) + 4::Int
+
+The splice will evaluate to (MkAge 3) and you can't add that to
+4::Int. So you can't coerce a (TExp Age) to a (TExp Int). -}
+
 ----------------------------------------------------
 -- Packaged versions for the programmer, hiding the Quasi-ness
 



More information about the ghc-commits mailing list