Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/cacfd03ec82329ec7c167295a19ee9b6a3f31f1e

>---------------------------------------------------------------

commit cacfd03ec82329ec7c167295a19ee9b6a3f31f1e
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Fri Nov 16 12:45:54 2012 +0000

    Test TypeHoles

>---------------------------------------------------------------

 tests/typecheck/should_compile/all.T         |    3 +++
 tests/typecheck/should_compile/holes.hs      |   15 +++++++++++++++
 tests/typecheck/should_compile/holes.stderr  |   26 ++++++++++++++++++++++++++
 tests/typecheck/should_compile/holes2.hs     |    7 +++++++
 tests/typecheck/should_compile/holes2.stderr |   20 ++++++++++++++++++++
 tests/typecheck/should_compile/holes3.hs     |   15 +++++++++++++++
 tests/typecheck/should_compile/holes3.stderr |   26 ++++++++++++++++++++++++++
 7 files changed, 112 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index 6240962..dd421ef 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -389,3 +389,6 @@ test('T7196', normal, compile, [''])
 test('T7050', normal, compile, [''])
 test('T7312', normal, compile, [''])
 test('T7384', normal, compile, [''])
+test('holes', normal, compile, ['-fdefer-type-errors'])
+test('holes2', normal, compile, ['-fdefer-type-errors'])
+test('holes3', normal, compile_fail, [''])
diff --git a/tests/typecheck/should_compile/holes.hs 
b/tests/typecheck/should_compile/holes.hs
new file mode 100644
index 0000000..fa5a892
--- /dev/null
+++ b/tests/typecheck/should_compile/holes.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE TypeHoles #-}
+
+module Main where
+
+main = return ()
+
+f = _
+
+g :: Int -> Char
+g x = _
+
+h = _ ++ "a"
+
+z :: [a] -> [a]
+z y = const y _
diff --git a/tests/typecheck/should_compile/holes.stderr 
b/tests/typecheck/should_compile/holes.stderr
new file mode 100644
index 0000000..626230f
--- /dev/null
+++ b/tests/typecheck/should_compile/holes.stderr
@@ -0,0 +1,26 @@
+
+holes.hs:7:5: Warning:
+    Found hole `_' with type t
+    Where: `t' is a rigid type variable bound by
+               the inferred type of f :: t at holes.hs:7:1
+    Relevant bindings include f :: t (bound at holes.hs:7:1)
+    In the expression: _
+    In an equation for `f': f = _
+
+holes.hs:10:7: Warning:
+    Found hole `_' with type Char
+    In the expression: _
+    In an equation for `g': g x = _
+
+holes.hs:12:5: Warning:
+    Found hole `_' with type [Char]
+    In the first argument of `(++)', namely `_'
+    In the expression: _ ++ "a"
+    In an equation for `h': h = _ ++ "a"
+
+holes.hs:15:15: Warning:
+    Found hole `_' with type b0
+    Where: `b0' is an ambiguous type variable
+    In the second argument of `const', namely `_'
+    In the expression: const y _
+    In an equation for `z': z y = const y _
diff --git a/tests/typecheck/should_compile/holes2.hs 
b/tests/typecheck/should_compile/holes2.hs
new file mode 100644
index 0000000..56614c7
--- /dev/null
+++ b/tests/typecheck/should_compile/holes2.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TypeHoles #-}
+
+module Main where
+
+main = return ()
+
+f = show _
diff --git a/tests/typecheck/should_compile/holes2.stderr 
b/tests/typecheck/should_compile/holes2.stderr
new file mode 100644
index 0000000..433b5a0
--- /dev/null
+++ b/tests/typecheck/should_compile/holes2.stderr
@@ -0,0 +1,20 @@
+
+holes2.hs:7:5: Warning:
+    No instance for (Show a0) arising from a use of `show'
+    The type variable `a0' is ambiguous
+    Possible fix: add a type signature that fixes these type variable(s)
+    Note: there are several potential instances:
+      instance Show Double -- Defined in `GHC.Float'
+      instance Show Float -- Defined in `GHC.Float'
+      instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
+        -- Defined in `GHC.Real'
+      ...plus 23 others
+    In the expression: show _
+    In an equation for `f': f = show _
+
+holes2.hs:7:10: Warning:
+    Found hole `_' with type a0
+    Where: `a0' is an ambiguous type variable
+    In the first argument of `show', namely `_'
+    In the expression: show _
+    In an equation for `f': f = show _
diff --git a/tests/typecheck/should_compile/holes3.hs 
b/tests/typecheck/should_compile/holes3.hs
new file mode 100644
index 0000000..fa5a892
--- /dev/null
+++ b/tests/typecheck/should_compile/holes3.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE TypeHoles #-}
+
+module Main where
+
+main = return ()
+
+f = _
+
+g :: Int -> Char
+g x = _
+
+h = _ ++ "a"
+
+z :: [a] -> [a]
+z y = const y _
diff --git a/tests/typecheck/should_compile/holes3.stderr 
b/tests/typecheck/should_compile/holes3.stderr
new file mode 100644
index 0000000..3bdba50
--- /dev/null
+++ b/tests/typecheck/should_compile/holes3.stderr
@@ -0,0 +1,26 @@
+
+holes3.hs:7:5:
+    Found hole `_' with type t
+    Where: `t' is a rigid type variable bound by
+               the inferred type of f :: t at holes3.hs:7:1
+    Relevant bindings include f :: t (bound at holes3.hs:7:1)
+    In the expression: _
+    In an equation for `f': f = _
+
+holes3.hs:10:7:
+    Found hole `_' with type Char
+    In the expression: _
+    In an equation for `g': g x = _
+
+holes3.hs:12:5:
+    Found hole `_' with type [Char]
+    In the first argument of `(++)', namely `_'
+    In the expression: _ ++ "a"
+    In an equation for `h': h = _ ++ "a"
+
+holes3.hs:15:15:
+    Found hole `_' with type b0
+    Where: `b0' is an ambiguous type variable
+    In the second argument of `const', namely `_'
+    In the expression: const y _
+    In an equation for `z': z y = const y _



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to