summaryrefslogtreecommitdiff
path: root/tests
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
parent9c299d282f943fd4db076b09b1901309e19308bd (diff)
Eliminated use of TH in test suite.
Diffstat (limited to 'tests')
-rw-r--r--tests/Tests/Helpers.hs31
-rw-r--r--tests/Tests/Readers/Markdown.hs2
-rw-r--r--tests/Tests/Readers/RST.hs37
-rw-r--r--tests/Tests/Writers/ConTeXt.hs36
-rw-r--r--tests/Tests/Writers/HTML.hs2
-rw-r--r--tests/Tests/Writers/LaTeX.hs2
-rw-r--r--tests/Tests/Writers/Markdown.hs2
7 files changed, 42 insertions, 70 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
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index 6498c6f07..33f5be670 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.Markdown (tests) where
import Text.Pandoc.Definition
diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs
index 0ad21f224..2876f4270 100644
--- a/tests/Tests/Readers/RST.hs
+++ b/tests/Tests/Readers/RST.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.RST (tests) where
import Text.Pandoc.Definition
@@ -20,24 +20,23 @@ tests :: [Test]
tests = [ "line block with blank line" =:
"| a\n|\n| b" =?> para (str "a") <>
para (str "\160b")
- , "field list" =:
- [_LIT|
-:Hostname: media08
-:IP address: 10.0.0.19
-:Size: 3ru
-:Date: 2001-08-16
-:Version: 1
-:Authors: - Me
- - Myself
- - I
-:Indentation: Since the field marker may be quite long, the second
- and subsequent lines of the field body do not have to line up
- with the first line, but they must be indented relative to the
- field name marker, and they must line up with each other.
-:Parameter i: integer
-:Final: item
- on two lines
-|] =?> ( setAuthors ["Me","Myself","I"]
+ , "field list" =: unlines
+ [ ":Hostname: media08"
+ , ":IP address: 10.0.0.19"
+ , ":Size: 3ru"
+ , ":Date: 2001-08-16"
+ , ":Version: 1"
+ , ":Authors: - Me"
+ , " - Myself"
+ , " - I"
+ , ":Indentation: Since the field marker may be quite long, the second"
+ , " and subsequent lines of the field body do not have to line up"
+ , " with the first line, but they must be indented relative to the"
+ , " field name marker, and they must line up with each other."
+ , ":Parameter i: integer"
+ , ":Final: item"
+ , " on two lines" ]
+ =?> ( setAuthors ["Me","Myself","I"]
$ setDate "2001-08-16"
$ doc
$ definitionList [ (str "Hostname", [para "media08"])
diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs
index 1beed33bb..8f0305adb 100644
--- a/tests/Tests/Writers/ConTeXt.hs
+++ b/tests/Tests/Writers/ConTeXt.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.ConTeXt (tests) where
import Test.Framework
@@ -48,23 +48,23 @@ tests = [ testGroup "inline code"
[ "nested" =:
bulletList [
plain (text "top")
- <> bulletList [
- plain (text "next")
- <> bulletList [plain (text "bot")]
- ]
- ] =?> [_LIT|
-\startitemize[packed]
-\item
- top
- \startitemize[packed]
- \item
- next
- \startitemize[packed]
- \item
- bot
- \stopitemize
- \stopitemize
-\stopitemize|]
+ <> bulletList [
+ plain (text "next")
+ <> bulletList [plain (text "bot")]
+ ]
+ ] =?> unlines
+ [ "\\startitemize[packed]"
+ , "\\item"
+ , " top"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " next"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " bot"
+ , " \\stopitemize"
+ , " \\stopitemize"
+ , "\\stopitemize" ]
]
]
diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs
index 5d6e301c5..dad1d0880 100644
--- a/tests/Tests/Writers/HTML.hs
+++ b/tests/Tests/Writers/HTML.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.HTML (tests) where
import Test.Framework
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index 33d6ecc78..944d6c138 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.LaTeX (tests) where
import Test.Framework
diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs
index 22ce8b27c..99b85dfb7 100644
--- a/tests/Tests/Writers/Markdown.hs
+++ b/tests/Tests/Writers/Markdown.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Markdown (tests) where
import Test.Framework