summaryrefslogtreecommitdiff
path: root/testsuite/tests/th
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/th')
-rw-r--r--testsuite/tests/th/T5358.stderr11
-rw-r--r--testsuite/tests/th/TH_reifyDecl1.hs3
-rw-r--r--testsuite/tests/th/TH_reifyDecl1.stderr66
-rw-r--r--testsuite/tests/th/TH_reifyMkName.hs3
-rw-r--r--testsuite/tests/th/TH_reifyMkName.stderr4
5 files changed, 32 insertions, 55 deletions
diff --git a/testsuite/tests/th/T5358.stderr b/testsuite/tests/th/T5358.stderr
index 4a1bfbd5fe..01f1ffa608 100644
--- a/testsuite/tests/th/T5358.stderr
+++ b/testsuite/tests/th/T5358.stderr
@@ -1,15 +1,24 @@
T5358.hs:7:1:
+ Couldn't match expected type `t1 -> t1' with actual type `Int'
The equation(s) for `t1' have one argument,
but its type `Int' has none
T5358.hs:8:1:
+ Couldn't match expected type `t0 -> t0' with actual type `Int'
The equation(s) for `t2' have one argument,
but its type `Int' has none
T5358.hs:10:13:
+ Couldn't match expected type `t0 -> a0' with actual type `Int'
The function `t1' is applied to one argument,
but its type `Int' has none
In the first argument of `(==)', namely `t1 x'
In the expression: t1 x == t2 x
- In an equation for `prop_x1': prop_x1 x = t1 x == t2 x
+
+T5358.hs:10:21:
+ Couldn't match expected type `t0 -> a0' with actual type `Int'
+ The function `t2' is applied to one argument,
+ but its type `Int' has none
+ In the second argument of `(==)', namely `t2 x'
+ In the expression: t1 x == t2 x
diff --git a/testsuite/tests/th/TH_reifyDecl1.hs b/testsuite/tests/th/TH_reifyDecl1.hs
index 9c0880b2af..f2f5dd8b0e 100644
--- a/testsuite/tests/th/TH_reifyDecl1.hs
+++ b/testsuite/tests/th/TH_reifyDecl1.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE TypeFamilies #-}
module TH_reifyDecl1 where
+import System.IO
import Language.Haskell.TH
import Text.PrettyPrint.HughesPJ
@@ -62,7 +63,7 @@ data instance DF2 Bool = DBool
test :: ()
test = $(let
display :: Name -> Q ()
- display q = do { i <- reify q; report False (pprint i) }
+ display q = do { i <- reify q; runIO $ hPutStrLn stderr (pprint i) }
in do { display ''T
; display ''R
; display ''List
diff --git a/testsuite/tests/th/TH_reifyDecl1.stderr b/testsuite/tests/th/TH_reifyDecl1.stderr
index 7f4ae8550f..82a4f572ce 100644
--- a/testsuite/tests/th/TH_reifyDecl1.stderr
+++ b/testsuite/tests/th/TH_reifyDecl1.stderr
@@ -1,67 +1,35 @@
-
-TH_reifyDecl1.hs:63:10:
- data TH_reifyDecl1.T = TH_reifyDecl1.A | TH_reifyDecl1.B
-
-TH_reifyDecl1.hs:63:10:
- data TH_reifyDecl1.R a_0 = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D
-
-TH_reifyDecl1.hs:63:10:
- data TH_reifyDecl1.List a_0
+data TH_reifyDecl1.T = TH_reifyDecl1.A | TH_reifyDecl1.B
+data TH_reifyDecl1.R a_0 = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D
+data TH_reifyDecl1.List a_0
= TH_reifyDecl1.Nil
| TH_reifyDecl1.Cons a_0 (TH_reifyDecl1.List a_0)
-
-TH_reifyDecl1.hs:63:10:
- data TH_reifyDecl1.Tree a_0
+data TH_reifyDecl1.Tree a_0
= TH_reifyDecl1.Leaf
| (TH_reifyDecl1.Tree a_0) TH_reifyDecl1.:+: (TH_reifyDecl1.Tree a_0)
-
-TH_reifyDecl1.hs:63:10:
- type TH_reifyDecl1.IntList = [GHC.Types.Int]
-
-TH_reifyDecl1.hs:63:10:
- newtype TH_reifyDecl1.Length = TH_reifyDecl1.Length GHC.Types.Int
-
-TH_reifyDecl1.hs:63:10:
- Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall a_0 . TH_reifyDecl1.Tree a_0
-
-TH_reifyDecl1.hs:63:10:
- Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 =>
+type TH_reifyDecl1.IntList = [GHC.Types.Int]
+newtype TH_reifyDecl1.Length = TH_reifyDecl1.Length GHC.Types.Int
+Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall a_0 . TH_reifyDecl1.Tree a_0
+Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 =>
a_0 -> GHC.Types.Int
infixl 3 TH_reifyDecl1.m1
-
-TH_reifyDecl1.hs:63:10:
- class TH_reifyDecl1.C1 a_0
+class TH_reifyDecl1.C1 a_0
where TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 =>
a_0 -> GHC.Types.Int
-
-TH_reifyDecl1.hs:63:10:
- class TH_reifyDecl1.C2 a_0
+class TH_reifyDecl1.C2 a_0
where TH_reifyDecl1.m2 :: forall a_0 . TH_reifyDecl1.C2 a_0 =>
a_0 -> GHC.Types.Int
instance TH_reifyDecl1.C2 GHC.Types.Int
-
-TH_reifyDecl1.hs:63:10:
- class TH_reifyDecl1.C3 a_0
+class TH_reifyDecl1.C3 a_0
instance TH_reifyDecl1.C3 GHC.Types.Int
-
-TH_reifyDecl1.hs:63:10:
- type family TH_reifyDecl1.AT1 a_0 :: * -> *
+type family TH_reifyDecl1.AT1 a_0 :: * -> *
type instance TH_reifyDecl1.AT1 GHC.Types.Int = GHC.Types.Bool
-
-TH_reifyDecl1.hs:63:10:
- data family TH_reifyDecl1.AT2 a_0 :: * -> *
+data family TH_reifyDecl1.AT2 a_0 :: * -> *
data instance TH_reifyDecl1.AT2 GHC.Types.Int
= TH_reifyDecl1.AT2Int
-
-TH_reifyDecl1.hs:63:10: type family TH_reifyDecl1.TF1 a_0 :: * -> *
-
-TH_reifyDecl1.hs:63:10:
- type family TH_reifyDecl1.TF2 a_0 :: * -> *
+type family TH_reifyDecl1.TF1 a_0 :: * -> *
+type family TH_reifyDecl1.TF2 a_0 :: * -> *
type instance TH_reifyDecl1.TF2 GHC.Types.Bool = GHC.Types.Bool
-
-TH_reifyDecl1.hs:63:10: data family TH_reifyDecl1.DF1 a_0 :: * -> *
-
-TH_reifyDecl1.hs:63:10:
- data family TH_reifyDecl1.DF2 a_0 :: * -> *
+data family TH_reifyDecl1.DF1 a_0 :: * -> *
+data family TH_reifyDecl1.DF2 a_0 :: * -> *
data instance TH_reifyDecl1.DF2 GHC.Types.Bool
= TH_reifyDecl1.DBool
diff --git a/testsuite/tests/th/TH_reifyMkName.hs b/testsuite/tests/th/TH_reifyMkName.hs
index c5d5ebeea9..7c4d7196e0 100644
--- a/testsuite/tests/th/TH_reifyMkName.hs
+++ b/testsuite/tests/th/TH_reifyMkName.hs
@@ -2,12 +2,13 @@
module Foo where
+import System.IO
import Language.Haskell.TH
type C = Int
$(do
a <- reify $ mkName "C"
- report False $ show a
+ runIO $ hPutStrLn stderr (show a)
return []
)
diff --git a/testsuite/tests/th/TH_reifyMkName.stderr b/testsuite/tests/th/TH_reifyMkName.stderr
index 0537f1ddcf..a82707f987 100644
--- a/testsuite/tests/th/TH_reifyMkName.stderr
+++ b/testsuite/tests/th/TH_reifyMkName.stderr
@@ -1,3 +1 @@
-
-TH_reifyMkName.hs:9:3:
- TyConI (TySynD Foo.C [] (ConT GHC.Types.Int))
+TyConI (TySynD Foo.C [] (ConT GHC.Types.Int))