aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Readers/LaTeX.hs
diff options
context:
space:
mode:
authorIgor Pashev <pashev.igor@gmail.com>2021-07-17 18:10:34 +0200
committerIgor Pashev <pashev.igor@gmail.com>2021-07-17 18:46:16 +0200
commit48459559a13a20083fc9b31eb523b8ea2bf0a63f (patch)
tree1c04e75709457403110a6f8c5c90099f22369de3 /test/Tests/Readers/LaTeX.hs
parent0c39509d9b6a58958228cebf5d643598e5c98950 (diff)
parent46099e79defe662e541b12548200caf29063c1c6 (diff)
downloadpandoc-48459559a13a20083fc9b31eb523b8ea2bf0a63f.tar.gz
Merge branch 'master' of https://github.com/jgm/pandoc
Diffstat (limited to 'test/Tests/Readers/LaTeX.hs')
-rw-r--r--test/Tests/Readers/LaTeX.hs23
1 files changed, 2 insertions, 21 deletions
diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs
index c50c91ca1..4bda15140 100644
--- a/test/Tests/Readers/LaTeX.hs
+++ b/test/Tests/Readers/LaTeX.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.LaTeX
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -13,14 +12,9 @@ Tests for the LaTeX reader.
-}
module Tests.Readers.LaTeX (tests) where
-import Prelude
import Data.Text (Text)
import qualified Data.Text as T
-import qualified Text.Pandoc.UTF8 as UTF8
-import Text.Pandoc.Readers.LaTeX (tokenize, untokenize)
import Test.Tasty
-import Test.Tasty.HUnit
-import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@@ -49,21 +43,8 @@ simpleTable' aligns rows
where
toRow = Row nullAttr . map simpleCell
-tokUntokRt :: String -> Bool
-tokUntokRt s = untokenize (tokenize "random" t) == t
- where t = T.pack s
-
tests :: [TestTree]
-tests = [ testGroup "tokenization"
- [ testCase "tokenizer round trip on test case" $ do
- orig <- T.pack <$> UTF8.readFile "../test/latex-reader.latex"
- let new = untokenize $ tokenize "../test/latex-reader.latex"
- orig
- assertEqual "untokenize . tokenize is identity" orig new
- , testProperty "untokenize . tokenize is identity" tokUntokRt
- ]
-
- , testGroup "basic"
+tests = [ testGroup "basic"
[ "simple" =:
"word" =?> para "word"
, "space" =: