{-# LANGUAGE OverloadedStrings #-} module Tests.Writers.Docbook (tests) where import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers import Text.Pandoc.Arbitrary() docbook :: (ToPandoc a) => a -> String docbook = docbookWithOpts def{ writerWrapText = WrapNone } docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String docbookWithOpts opts = writeDocbook opts . toPandoc {- "my test" =: X =?> Y is shorthand for test docbook "my test" $ X =?> Y which is in turn shorthand for test docbook "my test" (X,Y) -} infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test (=:) = test docbook lineblock :: Blocks lineblock = para ("some text" <> linebreak <> "and more lines" <> linebreak <> "and again") lineblock_out :: [String] lineblock_out = [ "some text" , "and more lines" , "and again" ] tests :: [Test] tests = [ testGroup "line blocks" [ "none" =: para "This is a test" =?> unlines [ "" , " This is a test" , "" ] , "basic" =: lineblock =?> unlines lineblock_out , "blockquote" =: blockQuote lineblock =?> unlines ( [ "
" ] ++ lineblock_out ++ [ "
" ] ) , "footnote" =: para ("This is a test" <> note lineblock <> " of footnotes") =?> unlines ( [ "" , " This is a test" ] ++ lineblock_out ++ [ " of footnotes" , "" ] ) ] , testGroup "compact lists" [ testGroup "bullet" [ "compact" =: bulletList [plain "a", plain "b", plain "c"] =?> unlines [ "" , " " , " " , " a" , " " , " " , " " , " " , " b" , " " , " " , " " , " " , " c" , " " , " " , "" ] , "loose" =: bulletList [para "a", para "b", para "c"] =?> unlines [ "" , " " , " " , " a" , " " , " " , " " , " " , " b" , " " , " " , " " , " " , " c" , " " , " " , "" ] ] , testGroup "ordered" [ "compact" =: orderedList [plain "a", plain "b", plain "c"] =?> unlines [ "" , " " , " " , " a" , " " , " " , " " , " " , " b" , " " , " " , " " , " " , " c" , " " , " " , "" ] , "loose" =: orderedList [para "a", para "b", para "c"] =?> unlines [ "" , " " , " " , " a" , " " , " " , " " , " " , " b" , " " , " " , " " , " " , " c" , " " , " " , "" ] ] , testGroup "definition" [ "compact" =: definitionList [ ("an", [plain "apple" ]) , ("a", [plain "banana"]) , ("an", [plain "orange"])] =?> unlines [ "" , " " , " " , " an" , " " , " " , " " , " apple" , " " , " " , " " , " " , " " , " a" , " " , " " , " " , " banana" , " " , " " , " " , " " , " " , " an" , " " , " " , " " , " orange" , " " , " " , " " , "" ] , "loose" =: definitionList [ ("an", [para "apple" ]) , ("a", [para "banana"]) , ("an", [para "orange"])] =?> unlines [ "" , " " , " " , " an" , " " , " " , " " , " apple" , " " , " " , " " , " " , " " , " a" , " " , " " , " " , " banana" , " " , " " , " " , " " , " " , " an" , " " , " " , " " , " orange" , " " , " " , " " , "" ] ] ] , testGroup "writer options" $ [ testGroup "top-level division" $ let headers = header 1 (text "header1") <> header 2 (text "header2") <> header 3 (text "header3") docbookTopLevelDiv :: (ToPandoc a) => TopLevelDivision -> a -> String docbookTopLevelDiv division = docbookWithOpts def{ writerTopLevelDivision = division } in [ test (docbookTopLevelDiv TopLevelSection) "sections as top-level" $ headers =?> unlines [ "" , " header1" , " " , " header2" , " " , " header3" , " " , " " , " " , " " , "" ] , test (docbookTopLevelDiv TopLevelChapter) "chapters as top-level" $ headers =?> unlines [ "" , " header1" , " " , " header2" , " " , " header3" , " " , " " , " " , " " , "" ] , test (docbookTopLevelDiv TopLevelPart) "parts as top-level" $ headers =?> unlines [ "" , " header1" , " " , " header2" , " " , " header3" , " " , " " , " " , " " , "" ] , test (docbookTopLevelDiv TopLevelDefault) "default top-level" $ headers =?> unlines [ "" , " header1" , " " , " header2" , " " , " header3" , " " , " " , " " , " " , "" ] ] ] ]