summaryrefslogtreecommitdiff
path: root/testsuite/tests/th
diff options
context:
space:
mode:
authorsheaf <sam.derbyshire@gmail.com>2023-04-01 16:30:24 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2023-04-01 18:28:37 -0400
commit3b7bbb39f28c926f8cfd30744253a418854bee31 (patch)
treeef26c6952f6035af31af7ada635aeacc3a694a97 /testsuite/tests/th
parent3da693466fd3e6a609a1a77361c50ed1b141858d (diff)
downloadhaskell-3b7bbb39f28c926f8cfd30744253a418854bee31.tar.gz
TH: revert changes to GadtC & RecGadtC
Commit 3f374399 included a breaking-change to the template-haskell library when it made the GadtC and RecGadtC constructors take non-empty lists of names. As this has the potential to break many users' packages, we decided to revert these changes for now.
Diffstat (limited to 'testsuite/tests/th')
-rw-r--r--testsuite/tests/th/T10828.hs5
-rw-r--r--testsuite/tests/th/T10828b.hs3
-rw-r--r--testsuite/tests/th/T10828b.stderr2
-rw-r--r--testsuite/tests/th/T11345.hs5
4 files changed, 6 insertions, 9 deletions
diff --git a/testsuite/tests/th/T10828.hs b/testsuite/tests/th/T10828.hs
index d73b5015ae..1285174cce 100644
--- a/testsuite/tests/th/T10828.hs
+++ b/testsuite/tests/th/T10828.hs
@@ -6,7 +6,6 @@ module T10828 where
import Language.Haskell.TH hiding (Type)
import System.IO
import Data.Kind (Type)
-import qualified Data.List.NonEmpty as NE ( singleton )
$( do { decl <- [d| data family D a :: Type -> Type
data instance D Int Bool :: Type where
@@ -34,7 +33,7 @@ $( return
[ DataD [] (mkName "T")
[ PlainTV (mkName "a") () ]
(Just StarT)
- [ GadtC (NE.singleton (mkName "MkT"))
+ [ GadtC [mkName "MkT"]
[ ( Bang NoSourceUnpackedness NoSourceStrictness
, VarT (mkName "a")
)
@@ -47,7 +46,7 @@ $( return
, ForallC [PlainTV (mkName "a") SpecifiedSpec, PlainTV (mkName "b") SpecifiedSpec]
[AppT (AppT EqualityT (VarT $ mkName "a" ) )
(ConT $ mkName "Int") ] $
- RecGadtC (NE.singleton (mkName "MkC"))
+ RecGadtC [mkName "MkC"]
[ ( mkName "foo"
, Bang NoSourceUnpackedness NoSourceStrictness
, VarT (mkName "a")
diff --git a/testsuite/tests/th/T10828b.hs b/testsuite/tests/th/T10828b.hs
index 36e91eb11a..4ea4d82f9c 100644
--- a/testsuite/tests/th/T10828b.hs
+++ b/testsuite/tests/th/T10828b.hs
@@ -4,7 +4,6 @@ module T10828b where
import Language.Haskell.TH
import System.IO
-import qualified Data.List.NonEmpty as NE ( singleton )
-- attempting to mix GADT and normal constructors
$( return
@@ -24,7 +23,7 @@ $( return
[AppT (AppT EqualityT (VarT $ mkName "a" ) )
(ConT $ mkName "Int") ] $
RecGadtC
- (NE.singleton (mkName "MkC"))
+ [mkName "MkC"]
[ ( mkName "foo"
, Bang NoSourceUnpackedness NoSourceStrictness
, VarT (mkName "a")
diff --git a/testsuite/tests/th/T10828b.stderr b/testsuite/tests/th/T10828b.stderr
index 6e78ca9087..357c86c458 100644
--- a/testsuite/tests/th/T10828b.stderr
+++ b/testsuite/tests/th/T10828b.stderr
@@ -1,5 +1,5 @@
-T10828b.hs:10:2: error: [GHC-24104]
+T10828b.hs:9:2: error: [GHC-24104]
Cannot mix GADT constructors with Haskell 98 constructors
When splicing a TH declaration:
data T a :: *
diff --git a/testsuite/tests/th/T11345.hs b/testsuite/tests/th/T11345.hs
index 11de6d8bd5..2288cdad15 100644
--- a/testsuite/tests/th/T11345.hs
+++ b/testsuite/tests/th/T11345.hs
@@ -5,7 +5,6 @@
module Main (main) where
import Language.Haskell.TH
-import qualified Data.List.NonEmpty as NE ( singleton )
infixr 7 :***:
data GADT a where
@@ -17,11 +16,11 @@ $(do gadtName <- newName "GADT2"
infixName <- newName ":****:"
a <- newName "a"
return [ DataD [] gadtName [KindedTV a () StarT] Nothing
- [ GadtC (NE.singleton prefixName)
+ [ GadtC [prefixName]
[ (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
, (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
] (AppT (ConT gadtName) (ConT ''Int))
- , GadtC (NE.singleton infixName)
+ , GadtC [infixName]
[ (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
, (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
] (AppT (ConT gadtName) (ConT ''Int))