summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/parser/should_compile/DumpParsedAst.stderr3
-rw-r--r--testsuite/tests/parser/should_compile/DumpRenamedAst.stderr3
-rw-r--r--testsuite/tests/rename/should_compile/T19984.hs34
-rw-r--r--testsuite/tests/rename/should_compile/T19984.stderr20
-rw-r--r--testsuite/tests/rename/should_compile/T9778.hs8
-rw-r--r--testsuite/tests/rename/should_compile/T9778.stderr10
-rw-r--r--testsuite/tests/rename/should_compile/all.T1
7 files changed, 74 insertions, 5 deletions
diff --git a/testsuite/tests/parser/should_compile/DumpParsedAst.stderr b/testsuite/tests/parser/should_compile/DumpParsedAst.stderr
index 60230b3b63..38e55e1021 100644
--- a/testsuite/tests/parser/should_compile/DumpParsedAst.stderr
+++ b/testsuite/tests/parser/should_compile/DumpParsedAst.stderr
@@ -227,7 +227,8 @@
(L
(SrcSpanAnn (EpAnnNotUsed) { DumpParsedAst.hs:11:11-16 })
(HsOpTy
- (NoExtField)
+ (EpAnnNotUsed)
+ (NotPromoted)
(L
(SrcSpanAnn (EpAnnNotUsed) { DumpParsedAst.hs:11:11 })
(HsTyVar
diff --git a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
index 77061c1f84..cfaa1b102e 100644
--- a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
+++ b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
@@ -206,7 +206,8 @@
(L
(SrcSpanAnn (EpAnnNotUsed) { DumpRenamedAst.hs:13:11-16 })
(HsOpTy
- (NoExtField)
+ (EpAnnNotUsed)
+ (NotPromoted)
(L
(SrcSpanAnn (EpAnnNotUsed) { DumpRenamedAst.hs:13:11 })
(HsTyVar
diff --git a/testsuite/tests/rename/should_compile/T19984.hs b/testsuite/tests/rename/should_compile/T19984.hs
new file mode 100644
index 0000000000..355fcdda64
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T19984.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeOperators #-}
+
+module T19984 where
+
+data D a = (:-) a a
+
+-- promoted datacons missing promotion tick
+-- (should give warnings with -fwarn-unticked-promoted-constructors)
+type A1 = Int : '[]
+type B1 = [Int, Bool]
+type C1 = (:) Int '[]
+type E1 = Int :- Bool
+type F1 = (:-) Int Bool
+
+-- promoted datacons with promotion ticks
+-- (no warnings)
+type A2 = Int ': '[]
+type B2 = '[Int, Bool]
+type C2 = '(:) Int '[]
+type E2 = Int ':- Bool
+type F2 = '(:-) Int Bool
+
+-- non-promoted datacons
+-- (no warnings)
+data G = GA | GB
+a3, b3, c3 :: [G]
+a3 = GA : []
+b3 = [GA, GB]
+c3 = (:) GA []
+
+e3, f3 :: D G
+e3 = GA :- GB
+f3 = (:-) GA GB
diff --git a/testsuite/tests/rename/should_compile/T19984.stderr b/testsuite/tests/rename/should_compile/T19984.stderr
new file mode 100644
index 0000000000..1f814797be
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T19984.stderr
@@ -0,0 +1,20 @@
+
+T19984.hs:10:15: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted constructor: :
+ Suggested fix: Use ': instead of :
+
+T19984.hs:11:11: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted list.
+ Suggested fix: Add a promotion tick, e.g. '[x,y,z].
+
+T19984.hs:12:11: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted constructor: (:).
+ Suggested fix: Use '(:) instead of (:).
+
+T19984.hs:13:15: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted constructor: :-
+ Suggested fix: Use ':- instead of :-
+
+T19984.hs:14:11: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted constructor: (:-).
+ Suggested fix: Use '(:-) instead of (:-).
diff --git a/testsuite/tests/rename/should_compile/T9778.hs b/testsuite/tests/rename/should_compile/T9778.hs
index 5b32f6763f..1ced4fbab5 100644
--- a/testsuite/tests/rename/should_compile/T9778.hs
+++ b/testsuite/tests/rename/should_compile/T9778.hs
@@ -1,8 +1,16 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
+{-# LANGUAGE TypeOperators #-}
+
module T9778 where
+import Data.Kind
+
data T = A | B
data G a where
C :: G A
+
+data D = MkD Type Type
+
+type S = Int `MkD` Bool
diff --git a/testsuite/tests/rename/should_compile/T9778.stderr b/testsuite/tests/rename/should_compile/T9778.stderr
index 99b93c104c..24a9c3c958 100644
--- a/testsuite/tests/rename/should_compile/T9778.stderr
+++ b/testsuite/tests/rename/should_compile/T9778.stderr
@@ -1,4 +1,8 @@
-T9778.hs:8:10: warning: [-Wunticked-promoted-constructors]
- Unticked promoted constructor: ‘A’.
- Suggested fix: Use ‘'A’ instead of ‘A’.
+T9778.hs:12:10: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted constructor: A.
+ Suggested fix: Use 'A instead of A.
+
+T9778.hs:16:14: warning: [-Wunticked-promoted-constructors]
+ Unticked promoted constructor: `MkD`.
+ Suggested fix: Use '`MkD` instead of `MkD`.
diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T
index 563eb3604f..e81bc0e4c8 100644
--- a/testsuite/tests/rename/should_compile/all.T
+++ b/testsuite/tests/rename/should_compile/all.T
@@ -187,3 +187,4 @@ test('T20609c', normal, compile, [''])
test('T20609d', normal, compile, [''])
test('T18862', normal, compile, [''])
test('unused_haddock', normal, compile, ['-haddock -Wall'])
+test('T19984', normal, compile, ['-fwarn-unticked-promoted-constructors'])