[commit: ghc] wip/custom-type-errors: Add some tests. (3f82e93)

git at git.haskell.org git at git.haskell.org
Wed Nov 11 21:51:45 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/custom-type-errors
Link       : http://ghc.haskell.org/trac/ghc/changeset/3f82e9326f9d4f52680ff3a59d39322f4c5539e3/ghc

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

commit 3f82e9326f9d4f52680ff3a59d39322f4c5539e3
Author: Iavor S. Diatchki <diatchki at galois.com>
Date:   Wed Nov 11 13:51:43 2015 -0800

    Add some tests.


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

3f82e9326f9d4f52680ff3a59d39322f4c5539e3
 .../tests/typecheck/should_fail/CustomTypeErrors01.hs | 14 ++++++++++++++
 .../typecheck/should_fail/CustomTypeErrors01.stderr   |  5 +++++
 .../tests/typecheck/should_fail/CustomTypeErrors02.hs | 19 +++++++++++++++++++
 .../typecheck/should_fail/CustomTypeErrors02.stderr   | 10 ++++++++++
 .../tests/typecheck/should_fail/CustomTypeErrors03.hs |  7 +++++++
 .../typecheck/should_fail/CustomTypeErrors03.stderr   |  5 +++++
 testsuite/tests/typecheck/should_fail/all.T           |  5 +++++
 7 files changed, 65 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors01.hs b/testsuite/tests/typecheck/should_fail/CustomTypeErrors01.hs
new file mode 100644
index 0000000..c44da1d
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors01.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE DataKinds, UndecidableInstances #-}
+module T1 where
+import GHC.TypeLits
+
+
+data MyType = MyType
+
+instance
+  TypeError (Text "Values of type 'MyType' cannot be compared for equality.")
+    => Eq MyType where (==) = undefined
+
+err x = x == MyType
+
+
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors01.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors01.stderr
new file mode 100644
index 0000000..d95de09
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors01.stderr
@@ -0,0 +1,5 @@
+
+CustomTypeErrors01.hs:12:11: error:
+    Values of type 'MyType' cannot be compared for equality.
+    In the expression: x == MyType
+    In an equation for ‘err’: err x = x == MyType
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.hs b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.hs
new file mode 100644
index 0000000..06eb234
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE DataKinds, UndecidableInstances #-}
+{-# LANGUAGE TypeFamilies, TypeOperators, FlexibleContexts #-}
+module T2 where
+
+import GHC.TypeLits
+
+type family IntRep a where
+  IntRep Int      = Integer
+  IntRep Integer  = Integer
+  IntRep Bool     = Integer
+  IntRep a        = TypeError (Text "The type '" :<>: ShowType a :<>:
+                               Text "' cannot be represented as an integer.")
+
+convert :: Num (IntRep a) => a -> IntRep a
+convert _ = 5
+
+err = convert id
+
+
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr
new file mode 100644
index 0000000..d15637c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr
@@ -0,0 +1,10 @@
+
+CustomTypeErrors02.hs:17:1: error:
+    The type 'a_aBf -> a_aBf' cannot be represented as an integer.
+    When checking that ‘err’ has the inferred type
+      err :: (TypeError ...)
+
+CustomTypeErrors02.hs:17:7: error:
+    The type 'a0 -> a0' cannot be represented as an integer.
+    In the expression: convert id
+    In an equation for ‘err’: err = convert id
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors03.hs b/testsuite/tests/typecheck/should_fail/CustomTypeErrors03.hs
new file mode 100644
index 0000000..8c12227
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors03.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE DataKinds #-}
+module T3 where
+
+import GHC.TypeLits
+
+f :: TypeError (Text "This is a type error")
+f = undefined
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors03.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors03.stderr
new file mode 100644
index 0000000..330fadb
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors03.stderr
@@ -0,0 +1,5 @@
+
+CustomTypeErrors03.hs:6:6: error:
+    This is a type error
+    In the type signature for ‘f’:
+      f :: TypeError (Text "This is a type error")
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 0a222bd..c2ec105 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -390,3 +390,8 @@ test('T10715', normal, compile_fail, [''])
 test('T10715b', normal, compile_fail, [''])
 test('T10971b', normal, compile_fail, [''])
 test('T10971d', extra_clean(['T10971c.hi', 'T10971c.o']), multimod_compile_fail, ['T10971d','-v0'])
+test('CustomTypeErrors01', normal, compile_fail, [''])
+test('CustomTypeErrors02', normal, compile_fail, [''])
+test('CustomTypeErrors03', normal, compile_fail, [''])
+
+



More information about the ghc-commits mailing list