summaryrefslogtreecommitdiff
path: root/testsuite/tests/parser
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/parser')
-rw-r--r--testsuite/tests/parser/should_compile/T2245.stderr6
-rw-r--r--testsuite/tests/parser/should_compile/VtaParse.hs63
-rw-r--r--testsuite/tests/parser/should_compile/all.T1
-rw-r--r--testsuite/tests/parser/should_compile/read014.stderr8
-rw-r--r--testsuite/tests/parser/should_fail/readFail003.stderr4
5 files changed, 73 insertions, 9 deletions
diff --git a/testsuite/tests/parser/should_compile/T2245.stderr b/testsuite/tests/parser/should_compile/T2245.stderr
index 1f5f87f7c7..783b751b34 100644
--- a/testsuite/tests/parser/should_compile/T2245.stderr
+++ b/testsuite/tests/parser/should_compile/T2245.stderr
@@ -13,10 +13,10 @@ T2245.hs:5:10: warning:
T2245.hs:7:29: warning:
• Defaulting the following constraints to type ‘T’
- (Fractional b0)
+ (Fractional a0)
arising from the literal ‘1e400’ at T2245.hs:7:29-33
- (Ord b0) arising from a use of ‘<’ at T2245.hs:7:27
- (Read b0) arising from a use of ‘read’ at T2245.hs:7:38-41
+ (Ord a0) arising from an operator section at T2245.hs:7:27-33
+ (Read a0) arising from a use of ‘read’ at T2245.hs:7:38-41
• In the second argument of ‘(<)’, namely ‘1e400’
In the first argument of ‘(.)’, namely ‘(< 1e400)’
In the second argument of ‘(.)’, namely ‘(< 1e400) . read’
diff --git a/testsuite/tests/parser/should_compile/VtaParse.hs b/testsuite/tests/parser/should_compile/VtaParse.hs
new file mode 100644
index 0000000000..b1cfd7d4d0
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/VtaParse.hs
@@ -0,0 +1,63 @@
+{-# LANGUAGE TypeApplications, RankNTypes, DataKinds, PolyKinds #-}
+
+module VtaParse where
+
+import Data.Proxy
+
+data Foo = Foo { first :: Int, second :: Bool} deriving Show
+
+f :: a -> b -> (a,b)
+f u v = (u, v)
+
+g :: Int -> Int -> (Int, Int)
+g u v = f @(Int) @Int u v
+
+dblTuple :: (a, b) -> ((a, b), b)
+dblTuple e@(_,y) = (e, y)
+
+
+-- interesting note:
+-- listpair :: forall a. [a] -> ([a], [a])
+-- therefore when explicitly applying, you do NOT put the type in "[ ]"
+
+listpair :: [a] -> ([a], [a])
+listpair [] = ([], [])
+listpair b@(_:_) = (b, b)
+
+-- suggested two cases by R. Eisenberg
+newtype N = MkN { unMkN :: forall a. Show a => a -> String }
+n = MkN show
+foo :: Bool -> String
+foo = unMkN n @Bool -- Fails without parens! Not anymore!
+
+(&&) :: Bool -> Bool -> Bool
+(b@True) && True = True
+_ && _ = False
+
+(*@&) :: a -> a -> (a, a)
+x *@& y = (x, y)
+
+(@&) :: a -> a -> (a, a)
+x @& y = (x, y)
+
+main :: IO ()
+main = do
+ print $ g 5 12
+ print $ ((id @String (concat ["hello ", "world ", []])):"Hamidhasan":[])
+ print $ dblTuple @(Foo) @String ((Foo 5 True), "hello")
+ print $ listpair @(Maybe Int) [Just 12, Nothing]
+ print $ listpair @(Maybe Bool) $ (Just True) : (Just False) : (Nothing @Bool) : []
+ print $ dblTuple @Foo @[Maybe Int] ((Foo 7 False), ([Just 5, Nothing]))
+ print $ 12 @& 5
+
+pro :: Proxy a -> ()
+pro _ = ()
+
+x = pro @'True
+
+(@@) :: Int -> Int -> Int
+(@@) = (+)
+
+five = 3 @@ 2
+
+silly = pro {- hi! -}@Int
diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T
index 0030040aed..9446bf1cfa 100644
--- a/testsuite/tests/parser/should_compile/all.T
+++ b/testsuite/tests/parser/should_compile/all.T
@@ -101,5 +101,6 @@ test('T5682', normal, compile, [''])
test('T9723a', normal, compile, [''])
test('T9723b', normal, compile, [''])
test('T10188', normal, compile, [''])
+test('VtaParse', normal, compile, [''])
test('T10196', normal, compile, [''])
test('T10582', expect_broken(10582), compile, [''])
diff --git a/testsuite/tests/parser/should_compile/read014.stderr b/testsuite/tests/parser/should_compile/read014.stderr
index 5302b3476e..ebc07af88e 100644
--- a/testsuite/tests/parser/should_compile/read014.stderr
+++ b/testsuite/tests/parser/should_compile/read014.stderr
@@ -1,13 +1,13 @@
-read014.hs:4:1: Warning:
+read014.hs:4:1: warning:
Top-level binding with no type signature:
ng1 :: forall r a. Num a => r -> a -> a
-read014.hs:4:5: Warning: Defined but not used: ‘x’
+read014.hs:4:5: warning: Defined but not used: ‘x’
-read014.hs:6:10: Warning:
+read014.hs:6:10: warning:
No explicit implementation for
‘+’, ‘*’, ‘abs’, ‘signum’, and ‘fromInteger’
In the instance declaration for ‘Num (a, b)’
-read014.hs:8:53: Warning: Defined but not used: ‘x’
+read014.hs:8:53: warning: Defined but not used: ‘x’
diff --git a/testsuite/tests/parser/should_fail/readFail003.stderr b/testsuite/tests/parser/should_fail/readFail003.stderr
index 8b9b4d0295..e837eeedd1 100644
--- a/testsuite/tests/parser/should_fail/readFail003.stderr
+++ b/testsuite/tests/parser/should_fail/readFail003.stderr
@@ -1,7 +1,7 @@
readFail003.hs:4:27: error:
• Occurs check: cannot construct the infinite type:
- r ~ (r, [a], [a1])
+ t ~ (t, [a], [a1])
• In the expression: a
In a pattern binding:
~(a, b, c)
@@ -11,6 +11,6 @@ readFail003.hs:4:27: error:
where
nullity = null
• Relevant bindings include
- a :: r (bound at readFail003.hs:4:3)
+ a :: t (bound at readFail003.hs:4:3)
b :: [a] (bound at readFail003.hs:4:5)
c :: [a1] (bound at readFail003.hs:4:7)