[commit: ghc] master: Add pragCompleteDName to templateHaskellNames (e4ab8ba)
git at git.haskell.org
git at git.haskell.org
Thu Jan 26 04:36:25 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/e4ab8ba72af27cd23ecd3737b166b625190c34a5/ghc
>---------------------------------------------------------------
commit e4ab8ba72af27cd23ecd3737b166b625190c34a5
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Wed Jan 25 23:32:17 2017 -0500
Add pragCompleteDName to templateHaskellNames
95dc6dc070deac733d4a4a63a93e606a2e772a67 forgot to add `pragCompleteDName`
to the list of `templateHaskellNames`, which caused a panic if you actually
tried to splice a `COMPLETE` pragma using Template Haskell. This applies the
easy fix and augments the regression test to check for this in the future.
>---------------------------------------------------------------
e4ab8ba72af27cd23ecd3737b166b625190c34a5
compiler/prelude/THNames.hs | 2 +-
testsuite/tests/th/T13098.hs | 18 ++++++++++++++++++
2 files changed, 19 insertions(+), 1 deletion(-)
diff --git a/compiler/prelude/THNames.hs b/compiler/prelude/THNames.hs
index e051082..253a89b 100644
--- a/compiler/prelude/THNames.hs
+++ b/compiler/prelude/THNames.hs
@@ -67,7 +67,7 @@ templateHaskellNames = [
classDName, instanceWithOverlapDName,
standaloneDerivWithStrategyDName, sigDName, forImpDName,
pragInlDName, pragSpecDName, pragSpecInlDName, pragSpecInstDName,
- pragRuleDName, pragAnnDName, defaultSigDName,
+ pragRuleDName, pragCompleteDName, pragAnnDName, defaultSigDName,
dataFamilyDName, openTypeFamilyDName, closedTypeFamilyDName,
dataInstDName, newtypeInstDName, tySynInstDName,
infixLDName, infixRDName, infixNDName,
diff --git a/testsuite/tests/th/T13098.hs b/testsuite/tests/th/T13098.hs
index 77e23f3..8df07d2 100644
--- a/testsuite/tests/th/T13098.hs
+++ b/testsuite/tests/th/T13098.hs
@@ -1,4 +1,6 @@
+{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE ViewPatterns #-}
module T13098 where
@@ -7,3 +9,19 @@ import Language.Haskell.TH
$( sequence [ dataD (cxt []) (mkName "T") [PlainTV (mkName "a")]
Nothing [normalC (mkName "T") []] []
, pragCompleteD [mkName "T"] Nothing ] )
+
+$([d| class LL f where
+ go :: f a -> ()
+
+ instance LL [] where
+ go _ = ()
+
+ pattern T2 :: LL f => f a
+ pattern T2 <- (go -> ())
+
+ {-# COMPLETE T2 :: [] #-}
+
+ -- No warning
+ foo :: [a] -> Int
+ foo T2 = 5
+ |])
More information about the ghc-commits
mailing list