Eliminated use of TH in test suite.

This commit is contained in:
John MacFarlane 2013-01-23 08:47:43 -08:00
parent 9c299d282f
commit daeb52d4e0
8 changed files with 43 additions and 72 deletions

View file

@ -384,7 +384,6 @@ Test-Suite test-pandoc
test-framework-quickcheck2 >= 0.2.9 && < 0.4,
QuickCheck >= 2.4 && < 2.6,
HUnit >= 1.2 && < 1.3,
template-haskell >= 2.4 && < 2.9,
containers >= 0.1 && < 0.6,
ansi-terminal == 0.5.*
Other-Modules: Tests.Old
@ -411,7 +410,7 @@ Test-Suite test-pandoc
else
cpp-options: -D_LIT=$lit
Default-Language: Haskell98
Default-Extensions: CPP, TemplateHaskell, QuasiQuotes
Default-Extensions: CPP
benchmark benchmark-pandoc
Type: exitcode-stdio-1.0

View file

@ -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

View file

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.Markdown (tests) where
import Text.Pandoc.Definition

View file

@ -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"])

View file

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.ConTeXt (tests) where
import Test.Framework
@ -52,19 +52,19 @@ tests = [ testGroup "inline code"
plain (text "next")
<> bulletList [plain (text "bot")]
]
] =?> [_LIT|
\startitemize[packed]
\item
top
\startitemize[packed]
\item
next
\startitemize[packed]
\item
bot
\stopitemize
\stopitemize
\stopitemize|]
] =?> unlines
[ "\\startitemize[packed]"
, "\\item"
, " top"
, " \\startitemize[packed]"
, " \\item"
, " next"
, " \\startitemize[packed]"
, " \\item"
, " bot"
, " \\stopitemize"
, " \\stopitemize"
, "\\stopitemize" ]
]
]

View file

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.HTML (tests) where
import Test.Framework

View file

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.LaTeX (tests) where
import Test.Framework

View file

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Markdown (tests) where
import Test.Framework