[commit: ghc] master: Fix #14888 by adding more special cases for ArrowT (6ee831f)
git at git.haskell.org
git at git.haskell.org
Mon Mar 5 14:00:16 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/6ee831f279c91888ee5815f8eee473bcd6fd25c6/ghc
>---------------------------------------------------------------
commit 6ee831f279c91888ee5815f8eee473bcd6fd25c6
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Mon Mar 5 08:57:04 2018 -0500
Fix #14888 by adding more special cases for ArrowT
Summary:
There were previously some situations where `(->)` would
not be desugared or reified as `ArrowT`, leading to various oddities
such as those observed in #14888. We now uniformly treat `(->)` as
`ArrowT` in Template Haskell–world by checking for any tycon that
has the same name as `(->)`, and converting that to `ArrowT`.
Test Plan: make test TEST=T14888
Reviewers: goldfire, bgamari, simonpj
Reviewed By: goldfire, simonpj
Subscribers: simonpj, rwbarton, thomie, carter
GHC Trac Issues: #14888
Differential Revision: https://phabricator.haskell.org/D4466
>---------------------------------------------------------------
6ee831f279c91888ee5815f8eee473bcd6fd25c6
compiler/deSugar/DsMeta.hs | 1 +
compiler/typecheck/TcSplice.hs | 1 +
testsuite/tests/th/T14888.hs | 18 ++++++++++++++++++
testsuite/tests/th/T14888.stderr | 11 +++++++++++
testsuite/tests/th/all.T | 2 ++
5 files changed, 33 insertions(+)
diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index db25c55..5029f9d 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -994,6 +994,7 @@ repTy ty@(HsQualTy {}) = repForall ty
repTy (HsTyVar _ (L _ n))
| isLiftedTypeKindTyConName n = repTStar
| n `hasKey` constraintKindTyConKey = repTConstraint
+ | n `hasKey` funTyConKey = repArrowTyCon
| isTvOcc occ = do tv1 <- lookupOcc n
repTvar tv1
| isDataOcc occ = do tc1 <- lookupOcc n
diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs
index 45e18e6..00591d1 100644
--- a/compiler/typecheck/TcSplice.hs
+++ b/compiler/typecheck/TcSplice.hs
@@ -1881,6 +1881,7 @@ reify_tc_app tc tys
| isTupleTyCon tc = if isPromotedDataCon tc
then TH.PromotedTupleT arity
else TH.TupleT arity
+ | tc `hasKey` funTyConKey = TH.ArrowT
| tc `hasKey` listTyConKey = TH.ListT
| tc `hasKey` nilDataConKey = TH.PromotedNilT
| tc `hasKey` consDataConKey = TH.PromotedConsT
diff --git a/testsuite/tests/th/T14888.hs b/testsuite/tests/th/T14888.hs
new file mode 100644
index 0000000..e2bcec6
--- /dev/null
+++ b/testsuite/tests/th/T14888.hs
@@ -0,0 +1,18 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T14888 where
+
+import Language.Haskell.TH
+
+foo :: $([t| (->) Bool Bool |])
+foo x = x
+
+class Functor' f where
+ fmap' :: (a -> b) -> f a -> f b
+
+instance Functor' ((->) r) where
+ fmap' = (.)
+
+$(return [])
+
+functor'Instances :: String
+functor'Instances = $(reify ''Functor' >>= stringE . pprint)
diff --git a/testsuite/tests/th/T14888.stderr b/testsuite/tests/th/T14888.stderr
new file mode 100644
index 0000000..963937f
--- /dev/null
+++ b/testsuite/tests/th/T14888.stderr
@@ -0,0 +1,11 @@
+T14888.hs:6:10-30: Splicing type
+ [t| (->) Bool Bool |] ======> Bool -> Bool
+T14888.hs:15:3-11: Splicing declarations return [] ======>
+T14888.hs:18:23-59: Splicing expression
+ reify ''Functor' >>= stringE . pprint
+ ======>
+ "class T14888.Functor' (f_0 :: * -> *)
+ where T14888.fmap' :: forall (f_0 :: * ->
+ *) . T14888.Functor' f_0 =>
+ forall (a_1 :: *) (b_2 :: *) . (a_1 -> b_2) -> f_0 a_1 -> f_0 b_2
+instance T14888.Functor' ((->) r_3 :: * -> *)"
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 47e8a9c..e9f2838 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -403,3 +403,5 @@ test('T14838', [], multimod_compile,
['T14838.hs', '-v0 -Wincomplete-patterns ' + config.ghc_th_way_flags])
test('T14817', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T14843', normal, compile, ['-v0'])
+test('T14888', normal, compile,
+ ['-v0 -ddump-splices -dsuppress-uniques ' + config.ghc_th_way_flags])
More information about the ghc-commits
mailing list