summaryrefslogtreecommitdiff
path: root/tests/Tests/Helpers.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2013-01-23 08:47:43 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-01-23 19:26:39 -0800
commitdaeb52d4e0f21b0e1ad8c3ce17ee9f18a6394f63 (patch)
tree40a9791fdff806ce599635bd0c5d5fbfb54f8cdc /tests/Tests/Helpers.hs
parent9c299d282f943fd4db076b09b1901309e19308bd (diff)
Eliminated use of TH in test suite.
Diffstat (limited to 'tests/Tests/Helpers.hs')
-rw-r--r--tests/Tests/Helpers.hs31
1 files changed, 2 insertions, 29 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index d6cad345c..af64f5148 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -1,9 +1,7 @@
-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, TemplateHaskell #-}
+{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
-- Utility functions for the test suite.
-module Tests.Helpers ( lit
- , file
- , test
+module Tests.Helpers ( test
, (=?>)
, property
, ToString(..)
@@ -20,34 +18,9 @@ import Test.HUnit (assertBool)
import Text.Pandoc.Shared (normalize, trimr)
import Text.Pandoc.Options
import Text.Pandoc.Writers.Native (writeNative)
-import Language.Haskell.TH.Quote (QuasiQuoter(..))
-import Language.Haskell.TH.Syntax (Q, runIO)
import qualified Test.QuickCheck.Property as QP
import Data.Algorithm.Diff
-lit :: QuasiQuoter
-lit = QuasiQuoter {
- quoteExp = (\a -> let b = rnl a in [|b|]) . filter (/= '\r')
- , quotePat = error "Unimplemented"
- , quoteType = error "Unimplemented"
- , quoteDec = error "Unimplemented"
- }
- where rnl ('\n':xs) = xs
- rnl xs = xs
-
-file :: QuasiQuoter
-file = quoteFile lit
-
--- adapted from TH 2.5 code
-quoteFile :: QuasiQuoter -> QuasiQuoter
-quoteFile (QuasiQuoter { quoteExp = qe, quotePat = qp }) =
- QuasiQuoter { quoteExp = get qe, quotePat = get qp,
- quoteType = error "Unimplemented", quoteDec = error "Unimplemented" }
- where
- get :: (String -> Q a) -> String -> Q a
- get old_quoter file_name = do { file_cts <- runIO (readFile file_name)
- ; old_quoter file_cts }
-
test :: (ToString a, ToString b, ToString c)
=> (a -> b) -- ^ function to test
-> String -- ^ name of test case