diff options
author | Igor Pashev <pashev.igor@gmail.com> | 2021-07-17 18:10:34 +0200 |
---|---|---|
committer | Igor Pashev <pashev.igor@gmail.com> | 2021-07-17 18:46:16 +0200 |
commit | 48459559a13a20083fc9b31eb523b8ea2bf0a63f (patch) | |
tree | 1c04e75709457403110a6f8c5c90099f22369de3 /test/Tests/Writers/ConTeXt.hs | |
parent | 0c39509d9b6a58958228cebf5d643598e5c98950 (diff) | |
parent | 46099e79defe662e541b12548200caf29063c1c6 (diff) | |
download | pandoc-48459559a13a20083fc9b31eb523b8ea2bf0a63f.tar.gz |
Merge branch 'master' of https://github.com/jgm/pandoc
Diffstat (limited to 'test/Tests/Writers/ConTeXt.hs')
-rw-r--r-- | test/Tests/Writers/ConTeXt.hs | 237 |
1 files changed, 122 insertions, 115 deletions
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs index c747e5d2f..fbbf9b948 100644 --- a/test/Tests/Writers/ConTeXt.hs +++ b/test/Tests/Writers/ConTeXt.hs @@ -1,8 +1,6 @@ -{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.ConTeXt (tests) where -import Prelude import Data.Text (unpack, pack) import Test.Tasty import Test.Tasty.QuickCheck @@ -41,116 +39,125 @@ infix 4 =: (=:) = test context tests :: [TestTree] -tests = [ testGroup "inline code" - [ "with '}'" =: code "}" =?> "\\mono{\\}}" - , "without '}'" =: code "]" =?> "\\type{]}" - , testProperty "code property" $ \s -> null s || '\n' `elem` s || - if '{' `elem` s || '}' `elem` s - then context' (code $ pack s) == "\\mono{" ++ - context' (str $ pack s) ++ "}" - else context' (code $ pack s) == "\\type{" ++ s ++ "}" - ] - , testGroup "headers" - [ "level 1" =: - headerWith ("my-header",[],[]) 1 "My header" =?> "\\section[title={My header},reference={my-header}]" - , test contextDiv "section-divs" $ - ( headerWith ("header1", [], []) 1 (text "Header1") - <> headerWith ("header2", [], []) 2 (text "Header2") - <> headerWith ("header3", [], []) 3 (text "Header3") - <> headerWith ("header4", [], []) 4 (text "Header4") - <> headerWith ("header5", [], []) 5 (text "Header5") - <> headerWith ("header6", [], []) 6 (text "Header6")) - =?> - unlines [ "\\startsection[title={Header1},reference={header1}]\n" - , "\\startsubsection[title={Header2},reference={header2}]\n" - , "\\startsubsubsection[title={Header3},reference={header3}]\n" - , "\\startsubsubsubsection[title={Header4},reference={header4}]\n" - , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n" - , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n" - , "\\stopsubsubsubsubsubsection\n" - , "\\stopsubsubsubsubsection\n" - , "\\stopsubsubsubsection\n" - , "\\stopsubsubsection\n" - , "\\stopsubsection\n" - , "\\stopsection" ] - ] - , testGroup "bullet lists" - [ "nested" =: - bulletList [ - plain (text "top") - <> bulletList [ - plain (text "next") - <> bulletList [plain (text "bot")] - ] - ] =?> unlines - [ "\\startitemize[packed]" - , "\\item" - , " top" - , " \\startitemize[packed]" - , " \\item" - , " next" - , " \\startitemize[packed]" - , " \\item" - , " bot" - , " \\stopitemize" - , " \\stopitemize" - , "\\stopitemize" ] - ] - , testGroup "natural tables" - [ test contextNtb "table with header and caption" $ - let capt = text "Table 1" - aligns = [(AlignRight, ColWidthDefault), (AlignLeft, ColWidthDefault), (AlignCenter, ColWidthDefault), (AlignDefault, ColWidthDefault)] - headers = [plain $ text "Right", - plain $ text "Left", - plain $ text "Center", - plain $ text "Default"] - rows = [[plain $ text "1.1", - plain $ text "1.2", - plain $ text "1.3", - plain $ text "1.4"] - ,[plain $ text "2.1", - plain $ text "2.2", - plain $ text "2.3", - plain $ text "2.4"] - ,[plain $ text "3.1", - plain $ text "3.2", - plain $ text "3.3", - plain $ text "3.4"]] - toRow = Row nullAttr . map simpleCell - in table (simpleCaption $ plain capt) - aligns - (TableHead nullAttr [toRow headers]) - [TableBody nullAttr 0 [] $ map toRow rows] - (TableFoot nullAttr []) - =?> unlines [ "\\startplacetable[title={Table 1}]" - , "\\startTABLE" - , "\\startTABLEhead" - , "\\NC[align=left] Right" - , "\\NC[align=right] Left" - , "\\NC[align=middle] Center" - , "\\NC Default" - , "\\NC\\NR" - , "\\stopTABLEhead" - , "\\startTABLEbody" - , "\\NC[align=left] 1.1" - , "\\NC[align=right] 1.2" - , "\\NC[align=middle] 1.3" - , "\\NC 1.4" - , "\\NC\\NR" - , "\\NC[align=left] 2.1" - , "\\NC[align=right] 2.2" - , "\\NC[align=middle] 2.3" - , "\\NC 2.4" - , "\\NC\\NR" - , "\\stopTABLEbody" - , "\\startTABLEfoot" - , "\\NC[align=left] 3.1" - , "\\NC[align=right] 3.2" - , "\\NC[align=middle] 3.3" - , "\\NC 3.4" - , "\\NC\\NR" - , "\\stopTABLEfoot" - , "\\stopTABLE" - , "\\stopplacetable" ] - ] - ] +tests = + [ testGroup "inline code" + [ "with '}'" =: code "}" =?> "\\mono{\\}}" + , "without '}'" =: code "]" =?> "\\type{]}" + , "span with ID" =: + spanWith ("city", [], []) "Berlin" =?> + "\\reference[city]{}Berlin" + , testProperty "code property" $ \s -> null s || '\n' `elem` s || + if '{' `elem` s || '}' `elem` s + then context' (code $ pack s) == "\\mono{" ++ + context' (str $ pack s) ++ "}" + else context' (code $ pack s) == "\\type{" ++ s ++ "}" + ] + , testGroup "headers" + [ "level 1" =: + headerWith ("my-header",[],[]) 1 "My header" =?> + "\\section[title={My header},reference={my-header}]" + , test contextDiv "section-divs" $ + ( headerWith ("header1", [], []) 1 (text "Header1") + <> headerWith ("header2", [], []) 2 (text "Header2") + <> headerWith ("header3", [], []) 3 (text "Header3") + <> headerWith ("header4", [], []) 4 (text "Header4") + <> headerWith ("header5", [], []) 5 (text "Header5") + <> headerWith ("header6", [], []) 6 (text "Header6")) + =?> + unlines + [ "\\startsection[title={Header1},reference={header1}]\n" + , "\\startsubsection[title={Header2},reference={header2}]\n" + , "\\startsubsubsection[title={Header3},reference={header3}]\n" + , "\\startsubsubsubsection[title={Header4},reference={header4}]\n" + , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n" + , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n" + , "\\stopsubsubsubsubsubsection\n" + , "\\stopsubsubsubsubsection\n" + , "\\stopsubsubsubsection\n" + , "\\stopsubsubsection\n" + , "\\stopsubsection\n" + , "\\stopsection" ] + ] + , testGroup "bullet lists" + [ "nested" =: + bulletList [ + plain (text "top") + <> bulletList [ + plain (text "next") + <> bulletList [plain (text "bot")] + ] + ] =?> unlines + [ "\\startitemize[packed]" + , "\\item" + , " top" + , " \\startitemize[packed]" + , " \\item" + , " next" + , " \\startitemize[packed]" + , " \\item" + , " bot" + , " \\stopitemize" + , " \\stopitemize" + , "\\stopitemize" ] + ] + , testGroup "natural tables" + [ test contextNtb "table with header and caption" $ + let capt = text "Table 1" + aligns = [ (AlignRight, ColWidthDefault) + , (AlignLeft, ColWidthDefault) + , (AlignCenter, ColWidthDefault) + , (AlignDefault, ColWidthDefault) ] + headers = [plain $ text "Right", + plain $ text "Left", + plain $ text "Center", + plain $ text "Default"] + rows = [[plain $ text "1.1", + plain $ text "1.2", + plain $ text "1.3", + plain $ text "1.4"] + ,[plain $ text "2.1", + plain $ text "2.2", + plain $ text "2.3", + plain $ text "2.4"] + ,[plain $ text "3.1", + plain $ text "3.2", + plain $ text "3.3", + plain $ text "3.4"]] + toRow = Row nullAttr . map simpleCell + in table (simpleCaption $ plain capt) + aligns + (TableHead nullAttr [toRow headers]) + [TableBody nullAttr 0 [] $ map toRow rows] + (TableFoot nullAttr []) + =?> unlines [ "\\startplacetable[title={Table 1}]" + , "\\startTABLE" + , "\\startTABLEhead" + , "\\NC[align=left] Right" + , "\\NC[align=right] Left" + , "\\NC[align=middle] Center" + , "\\NC Default" + , "\\NC\\NR" + , "\\stopTABLEhead" + , "\\startTABLEbody" + , "\\NC[align=left] 1.1" + , "\\NC[align=right] 1.2" + , "\\NC[align=middle] 1.3" + , "\\NC 1.4" + , "\\NC\\NR" + , "\\NC[align=left] 2.1" + , "\\NC[align=right] 2.2" + , "\\NC[align=middle] 2.3" + , "\\NC 2.4" + , "\\NC\\NR" + , "\\stopTABLEbody" + , "\\startTABLEfoot" + , "\\NC[align=left] 3.1" + , "\\NC[align=right] 3.2" + , "\\NC[align=middle] 3.3" + , "\\NC 3.4" + , "\\NC\\NR" + , "\\stopTABLEfoot" + , "\\stopTABLE" + , "\\stopplacetable" ] + ] + ] |