aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--tests/Tests/Helpers.hs14
1 files changed, 14 insertions, 0 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index 91243e1ce..ed67cd1e4 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -2,6 +2,7 @@
-- Utility functions for the test suite.
module Tests.Helpers ( lit
+ , file
, test
, (=?>)
, property
@@ -20,6 +21,7 @@ import Text.Pandoc.Shared (normalize, defaultWriterOptions,
WriterOptions(..), removeTrailingSpace)
import Text.Pandoc.Writers.Native (writeNative)
import Language.Haskell.TH.Quote
+import Language.Haskell.TH.Syntax (Q, runIO)
import qualified Test.QuickCheck.Property as QP
lit :: QuasiQuoter
@@ -28,6 +30,18 @@ lit = QuasiQuoter ((\a -> let b = rnl a in [|b|]) . filter (/= '\r')) $
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 }
+ 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