aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--tests/golden-tests/tests/GADTRecords.hs2
-rw-r--r--tests/golden-tests/tests/QuasiExpr.hs8
-rw-r--r--tests/golden-tests/tests/QuasiQuote.hs2
3 files changed, 5 insertions, 7 deletions
diff --git a/tests/golden-tests/tests/GADTRecords.hs b/tests/golden-tests/tests/GADTRecords.hs
index a82cb381..c77810ad 100644
--- a/tests/golden-tests/tests/GADTRecords.hs
+++ b/tests/golden-tests/tests/GADTRecords.hs
@@ -1,4 +1,4 @@
-
+{-# LANGUAGE GADTs #-}
module GADTRecords (H1(..)) where
-- | h1
diff --git a/tests/golden-tests/tests/QuasiExpr.hs b/tests/golden-tests/tests/QuasiExpr.hs
index 6fc00a72..970759ba 100644
--- a/tests/golden-tests/tests/QuasiExpr.hs
+++ b/tests/golden-tests/tests/QuasiExpr.hs
@@ -5,20 +5,18 @@ module QuasiExpr where
import Language.Haskell.TH
import Language.Haskell.TH.Quote
-import Data.Typeable
-import Data.Generics
data Expr = IntExpr Integer
| AntiIntExpr String
| BinopExpr BinOp Expr Expr
| AntiExpr String
- deriving(Show, Typeable, Data)
+ deriving Show
data BinOp = AddOp
| SubOp
| MulOp
| DivOp
- deriving(Show, Typeable, Data)
+ deriving Show
eval :: Expr -> Integer
eval (IntExpr n) = n
@@ -29,7 +27,7 @@ eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y)
opToFun MulOp = (*)
opToFun DivOp = div
-expr = QuasiQuoter parseExprExp undefined
+expr = QuasiQuoter parseExprExp undefined undefined undefined
-- cheating...
parseExprExp :: String -> Q Exp
diff --git a/tests/golden-tests/tests/QuasiQuote.hs b/tests/golden-tests/tests/QuasiQuote.hs
index ed3c3787..06762cf9 100644
--- a/tests/golden-tests/tests/QuasiQuote.hs
+++ b/tests/golden-tests/tests/QuasiQuote.hs
@@ -6,4 +6,4 @@ module QuasiQuote where
import QuasiExpr
val :: Integer
-val = eval [$expr|1 + 2|]
+val = eval [expr|1 + 2|]