diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-02-04 12:56:30 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-02-04 12:56:30 +0100 |
commit | 18ab8642692caca2716fd9b5a0e6dbfd3d9cf9cc (patch) | |
tree | 05f4e9024093e233c131b3494e71265062ffd94a /tests/Tests/Writers/TEI.hs | |
parent | 8418c1a7d7e5312dfddbc011adb257552b2a864b (diff) | |
download | pandoc-18ab8642692caca2716fd9b5a0e6dbfd3d9cf9cc.tar.gz |
Moved tests/ -> test/.
Diffstat (limited to 'tests/Tests/Writers/TEI.hs')
-rw-r--r-- | tests/Tests/Writers/TEI.hs | 43 |
1 files changed, 0 insertions, 43 deletions
diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs deleted file mode 100644 index 703f565bb..000000000 --- a/tests/Tests/Writers/TEI.hs +++ /dev/null @@ -1,43 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} -module Tests.Writers.TEI (tests) where - -import Test.Framework -import Text.Pandoc.Builder -import Text.Pandoc -import Tests.Helpers -import Text.Pandoc.Arbitrary() - -{- - "my test" =: X =?> Y - -is shorthand for - - test html "my test" $ X =?> Y - -which is in turn shorthand for - - test html "my test" (X,Y) --} - -infix 4 =: -(=:) :: (ToString a, ToPandoc a) - => String -> (a, String) -> Test -(=:) = test (purely (writeTEI def) . toPandoc) - -tests :: [Test] -tests = [ testGroup "block elements" - ["para" =: para "Lorem ipsum cetera." - =?> "<p>Lorem ipsum cetera.</p>" - ] - , testGroup "inlines" - [ - "Emphasis" =: emph ("emphasized") - =?> "<p><hi rendition=\"simple:italic\">emphasized</hi></p>" - ,"SingleQuoted" =: singleQuoted (text "quoted material") - =?> "<p><quote>quoted material</quote></p>" - ,"DoubleQuoted" =: doubleQuoted (text "quoted material") - =?> "<p><quote>quoted material</quote></p>" - ,"NestedQuoted" =: doubleQuoted (singleQuoted (text "quoted material")) - =?> "<p><quote><quote>quoted material</quote></quote></p>" - ] - ] |