pandoc/test/Tests/Writers/FB2.hs
Alexander Krotov f224567d52 FB2 writer: represent HorizontalRule as empty line
HorizontalRule corresponds to <hr> element in the default output
format, HTML. Current HTML standard defines <hr> element as
"paragraph-level thematic break". In typography it is often
represented by extra space or centered asterism ("⁂"), but since
FB2 does not support text centering, empty line (similar to extra space)
is the only solution.

Line breaks, on the other hand, don't generate <empty-line />
anymore. Previously line breaks generated <empty-line /> element
inside paragraph, which is not allowed. So, this commit addresses
issue #2424 ("FB2 produced by pandoc doesn't validate").

FB2 does not have a way to represent line breaks inside paragraphs.
They are replaced with LF character, which is not rendered by
FB2 readers, but at least preserves some information.
2018-04-05 19:53:36 +03:00

36 lines
1.5 KiB
Haskell
Raw Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.FB2 (tests) where
import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
fb2 :: String -> String
fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++
"<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section>" ++ x ++ "</section></body></FictionBook>"
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeFB2 def) . toPandoc)
tests :: [TestTree]
tests = [ testGroup "block elements"
["para" =: para "Lorem ipsum cetera."
=?> fb2 "<p>Lorem ipsum cetera.</p>"
]
, testGroup "inlines"
[
"Emphasis" =: para (emph "emphasized")
=?> fb2 "<p><emphasis>emphasized</emphasis></p>"
]
, "bullet list" =: bulletList [ plain $ text "first"
, plain $ text "second"
, plain $ text "third"
]
=?> fb2 "<p>\x2022 first</p><p>\x2022 second</p><p>\x2022 third</p>"
]