summaryrefslogtreecommitdiff
path: root/testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs
diff options
context:
space:
mode:
authorsheaf <sam.derbyshire@gmail.com>2022-01-11 10:42:17 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-01-11 19:42:07 -0500
commit34d8bc24e33aa373acb6fdeef51427d968f28c0c (patch)
tree4eb89724f1b4e9e24ac3dc315497a5071ef463ef /testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs
parentaddf8e544841a3f7c818331e47fa89a2cbfb7b29 (diff)
downloadhaskell-34d8bc24e33aa373acb6fdeef51427d968f28c0c.tar.gz
Fix parsing & printing of unboxed sums
The pretty-printing of partially applied unboxed sums was incorrect, as we incorrectly dropped the first half of the arguments, even for a partial application such as (# | #) @IntRep @DoubleRep Int# which lead to the nonsensical (# DoubleRep | Int# #). This patch also allows users to write unboxed sum type constructors such as (# | #) :: TYPE r1 -> TYPE r2 -> TYPE (SumRep '[r1,r2]). Fixes #20858 and #20859.
Diffstat (limited to 'testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs')
-rw-r--r--testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs13
1 files changed, 13 insertions, 0 deletions
diff --git a/testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs b/testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs
new file mode 100644
index 0000000000..46ed1c13c1
--- /dev/null
+++ b/testsuite/tests/unboxedsums/UnboxedSumsTH_Fail.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE UnboxedSums #-}
+
+module UnboxedSumsTH_Fail where
+
+import Data.Proxy
+import Language.Haskell.TH
+
+-- (# | #) is not a valid data constructor,
+-- as it doesn't indicate which alternative we are taking.
+testDC :: (# Integer | Bool #)
+testDC = $( conE '(# | #) `appE` litE (IntegerL 77) )