summaryrefslogtreecommitdiff
path: root/testsuite/tests/parser/should_compile
diff options
context:
space:
mode:
authorJosh Meredith <joshmeredith2008@gmail.com>2019-12-04 23:39:28 +1100
committerJosh Meredith <joshmeredith2008@gmail.com>2019-12-04 23:39:28 +1100
commita8435165b84c32fd2ebdd1281dd6ee077e07ad5a (patch)
tree791936d014aeaa26174c2dcbef34c14f3329dd04 /testsuite/tests/parser/should_compile
parent7805441b4d5e22eb63a501e1e40383d10380dc92 (diff)
parentf03a41d4bf9418ee028ecb51654c928b2da74edd (diff)
downloadhaskell-wip/binary-readerT.tar.gz
Merge branch 'master' into wip/binary-readerTwip/binary-readerT
Diffstat (limited to 'testsuite/tests/parser/should_compile')
-rw-r--r--testsuite/tests/parser/should_compile/Proposal229f_instances.hs25
-rw-r--r--testsuite/tests/parser/should_compile/T1087.hs14
-rw-r--r--testsuite/tests/parser/should_compile/T16619.stderr3
-rw-r--r--testsuite/tests/parser/should_compile/all.T17
-rw-r--r--testsuite/tests/parser/should_compile/proposal-229a.hs8
-rw-r--r--testsuite/tests/parser/should_compile/proposal-229b.hs10
-rw-r--r--testsuite/tests/parser/should_compile/proposal-229d.hs6
-rw-r--r--testsuite/tests/parser/should_compile/proposal-229e.hs18
-rw-r--r--testsuite/tests/parser/should_compile/proposal-229f.hs13
-rw-r--r--testsuite/tests/parser/should_compile/proposal-229f.stderr4
10 files changed, 118 insertions, 0 deletions
diff --git a/testsuite/tests/parser/should_compile/Proposal229f_instances.hs b/testsuite/tests/parser/should_compile/Proposal229f_instances.hs
new file mode 100644
index 0000000000..2bd5a8ee19
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/Proposal229f_instances.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module Proposal229f_instances where
+
+import GHC.Exts
+import Data.String
+import Language.Haskell.TH
+import Language.Haskell.TH.Syntax
+
+instance IsList (Q (TExp String)) where
+ type Item (Q (TExp String)) = Char
+ fromList = liftTyped
+ toList = undefined
+
+instance IsList (Q Exp) where
+ type Item (Q Exp) = Char
+ fromList = lift
+ toList = undefined
+
+instance IsString (Q (TExp String)) where
+ fromString = liftTyped
+
+instance IsString (Q Exp) where
+ fromString = lift
diff --git a/testsuite/tests/parser/should_compile/T1087.hs b/testsuite/tests/parser/should_compile/T1087.hs
new file mode 100644
index 0000000000..9ad85e2b7a
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/T1087.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE BangPatterns #-}
+
+module T1087 where
+
+prefix_1 = let at a !b = False in at 1 2
+prefix_2 = let (.!.) a !b = False in 1 .!. 2
+
+infix_tilde_1 = let a `at` ~b = False in at 1 2
+infix_tilde_2 = let a .!. ~b = False in 1 .!. 2
+infix_tilde_3 = let ~a .!. b = False in 1 .!. 2
+
+infix_bang_1 = let a .!. !b = False in 1 .!. 2
+infix_bang_2 = let a `at` !b = False in at 1 2
+infix_bang_3 = let !a .!. b = False in 1 .!. 2
diff --git a/testsuite/tests/parser/should_compile/T16619.stderr b/testsuite/tests/parser/should_compile/T16619.stderr
new file mode 100644
index 0000000000..b5dfb89623
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/T16619.stderr
@@ -0,0 +1,3 @@
+
+T16619.hs:2:12: warning:
+ -Wmissing-space-after-bang is deprecated: bang patterns can no longer be written with a space
diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T
index 3d44e22510..91aae139ab 100644
--- a/testsuite/tests/parser/should_compile/all.T
+++ b/testsuite/tests/parser/should_compile/all.T
@@ -145,3 +145,20 @@ test('T16339', normal, compile, [''])
test('T16619', req_th, multimod_compile, ['T16619', '-v0'])
test('T504', normal, compile, [''])
test('T515', literate, compile, ['-Wall'])
+test('T1087', normal, compile, [''])
+test('proposal-229a', normal, compile, [''])
+test('proposal-229b', normal, compile, [''])
+test('proposal-229d', normal, compile, [''])
+test('proposal-229e', normal, compile, [''])
+
+# We omit 'profasm' because it fails with:
+# Cannot load -prof objects when GHC is built with -dynamic
+# To fix this, either:
+# (1) Use -fexternal-interpreter, or
+# (2) Build the program twice: once with -dynamic, and then
+# with -prof using -osuf to set a different object file suffix.
+test('proposal-229f',
+ [ extra_files(['proposal-229f.hs', 'Proposal229f_instances.hs']),
+ omit_ways(['profasm', 'profthreaded'])
+ ],
+ multimod_compile_and_run, ['proposal-229f.hs', ''])
diff --git a/testsuite/tests/parser/should_compile/proposal-229a.hs b/testsuite/tests/parser/should_compile/proposal-229a.hs
new file mode 100644
index 0000000000..c773cee3a2
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/proposal-229a.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE BangPatterns #-}
+
+module Proposal229a where
+
+data T a b = a :! b
+
+(!) :: x -> T a b -> (x, a, b)
+~u ! !(!m :! !n) = (u, m, n)
diff --git a/testsuite/tests/parser/should_compile/proposal-229b.hs b/testsuite/tests/parser/should_compile/proposal-229b.hs
new file mode 100644
index 0000000000..9182623e54
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/proposal-229b.hs
@@ -0,0 +1,10 @@
+module Proposal229b ((~), (@)) where
+
+(~) :: a -> b -> (a, b)
+x ~ y = (x, y)
+
+(@) :: a -> b -> (a, b)
+x @ y = (x, y)
+
+r :: ((Bool, Bool), Bool)
+r = True ~ False @ True
diff --git a/testsuite/tests/parser/should_compile/proposal-229d.hs b/testsuite/tests/parser/should_compile/proposal-229d.hs
new file mode 100644
index 0000000000..24a57ca872
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/proposal-229d.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE BangPatterns #-}
+
+module Proposal229d ((!)) where
+
+(!) :: a -> b -> (a, b)
+x ! y = (x,y) -- parsed as an operator even with BangPatterns enabled
diff --git a/testsuite/tests/parser/should_compile/proposal-229e.hs b/testsuite/tests/parser/should_compile/proposal-229e.hs
new file mode 100644
index 0000000000..d7fc35d38e
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/proposal-229e.hs
@@ -0,0 +1,18 @@
+{-# LANGUAGE BangPatterns #-}
+
+module Proposal229e ((!), f) where
+
+(!) :: Maybe a -> a -> (a, a)
+f :: a -> a
+
+-- the preceding '}' is not from a comment,
+-- so (!) is tight infix (therefore an operator)
+Nothing{}!x = (x, x)
+
+-- the following '{' opens a multi-line comment,
+-- so (!) is loose infix (therefore an operator)
+Just a !{-comment-}x = (a, x)
+
+-- the preceding '}' is closing a multi-line comment,
+-- so (!) is prefix (therefore a bang pattern)
+f{-comment-}!x = x
diff --git a/testsuite/tests/parser/should_compile/proposal-229f.hs b/testsuite/tests/parser/should_compile/proposal-229f.hs
new file mode 100644
index 0000000000..75b1341c6f
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/proposal-229f.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedLists #-}
+
+import System.IO
+import Proposal229f_instances
+
+-- Testing that we can parse $[...] and $"..."
+main = do
+ hPutStrLn stderr $['1','2','3']
+ hPutStrLn stderr $$['1','2','3']
+ hPutStrLn stderr $"123"
+ hPutStrLn stderr $$"123"
diff --git a/testsuite/tests/parser/should_compile/proposal-229f.stderr b/testsuite/tests/parser/should_compile/proposal-229f.stderr
new file mode 100644
index 0000000000..310be0621c
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/proposal-229f.stderr
@@ -0,0 +1,4 @@
+123
+123
+123
+123