From 25a9ca697a9fa3354e7a634d386efdef4031776f Mon Sep 17 00:00:00 2001 From: csforste Date: Thu, 24 Dec 2015 11:36:58 -0500 Subject: Add TEI Writer. --- tests/Tests/Writers/TEI.hs | 41 +++++++++++++++++++++++++++++++++++++++++ 1 file changed, 41 insertions(+) create mode 100644 tests/Tests/Writers/TEI.hs (limited to 'tests/Tests/Writers/TEI.hs') diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs new file mode 100644 index 000000000..228cda67d --- /dev/null +++ b/tests/Tests/Writers/TEI.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.TEI (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.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 (writeTEI def . toPandoc) + +tests :: [Test] +tests = [ testGroup "block elements" + ["para" =: para "Lorem ipsum cetera." + =?> "

Lorem ipsum cetera.

" + ] +-- ] +-- , testGroup "lists" +-- [ +-- ] + , testGroup "inlines" + [ + "Emphasis" =: emph ("emphasized") + =?> "emphasized" + ] + ] -- cgit v1.2.3 From 4d74a966c4dae72f627696e6440f8ac530965d6c Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 8 Jan 2016 17:33:37 -0800 Subject: Added some entity tests in Markdown reader tests. Change types of divs. From Docbook "sect#" and "simplesect" to "level#" and "section." Add tests. Add mention of TEI to README. Small changes to TEI writer. --- README | 15 ++++++++------- src/Text/Pandoc/Writers/TEI.hs | 12 ++++++------ tests/Tests/Writers/TEI.hs | 20 +++++++++++--------- 3 files changed, 25 insertions(+), 22 deletions(-) (limited to 'tests/Tests/Writers/TEI.hs') diff --git a/README b/README index 6d785721b..d0d0ddd6b 100644 --- a/README +++ b/README @@ -22,7 +22,7 @@ markup], [Haddock markup], [OPML], [Emacs Org mode], [DocBook], [OpenDocument], [ODT], [Word docx], [GNU Texinfo], [MediaWiki markup], [DokuWiki markup], [Haddock markup], [EPUB] (v2 or v3), [FictionBook2], [Textile], [groff man] pages, [Emacs Org mode], -[AsciiDoc], [InDesign ICML], and [Slidy], [Slideous], [DZSlides], +[AsciiDoc], [InDesign ICML], [TEI XML], and [Slidy], [Slideous], [DZSlides], [reveal.js] or [S5] HTML slide shows. It can also produce [PDF] output on systems where LaTeX, ConTeXt, or `wkhtmltopdf` is installed. @@ -89,6 +89,7 @@ Markdown can be expected to be lossy. [reveal.js]: http://lab.hakim.se/reveal-js/ [FictionBook2]: http://www.fictionbook.org/index.php/Eng:XML_Schema_Fictionbook_2.1 [InDesign ICML]: https://www.adobe.com/content/dam/Adobe/en/devnet/indesign/cs55-docs/IDML/idml-specification.pdf +[TEI Simple]: https://github.com/TEIC/TEI-Simple Using `pandoc` -------------- @@ -277,11 +278,11 @@ General options `docx` (Word docx), `haddock` (Haddock markup), `rtf` (rich text format), `epub` (EPUB v2 book), `epub3` (EPUB v3), `fb2` (FictionBook2 e-book), `asciidoc` (AsciiDoc), `icml` (InDesign - ICML), `slidy` (Slidy HTML and javascript slide show), `slideous` - (Slideous HTML and javascript slide show), `dzslides` (DZSlides - HTML5 + javascript slide show), `revealjs` (reveal.js HTML5 + - javascript slide show), `s5` (S5 HTML and javascript slide show), - or the path of a custom lua writer (see [Custom + ICML), `tei` (TEI Simple), `slidy` (Slidy HTML and javascript slide + show), `slideous` (Slideous HTML and javascript slide show), + `dzslides` (DZSlides HTML5 + javascript slide show), `revealjs` + (reveal.js HTML5 + javascript slide show), `s5` (S5 HTML and javascript + slide show), or the path of a custom lua writer (see [Custom writers], below). Note that `odt`, `epub`, and `epub3` output will not be directed to *stdout*; an output filename must be specified using the `-o/--output` option. If @@ -471,7 +472,7 @@ General writer options `-s`, `--standalone` : Produce output with an appropriate header and footer (e.g. a - standalone HTML, LaTeX, or RTF file, not a fragment). This option + standalone HTML, LaTeX, TEI, or RTF file, not a fragment). This option is set automatically for `pdf`, `epub`, `epub3`, `fb2`, `docx`, and `odt` output. diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index be9390de4..b9e683ab9 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -92,8 +92,8 @@ elementToTEI opts lvl (Sec _ _num (id',_,_) title elements) = else elements divType = case lvl of n | n == 0 -> "chapter" - | n >= 1 && n <= 5 -> "sect" ++ show n - | otherwise -> "simplesect" + | n >= 1 && n <= 5 -> "level" ++ show n + | otherwise -> "section" in inTags True "div" [("type", divType) | not (null id')] $ -- ("id", writerIdentifierPrefix opts ++ id') | not (null id')] $ inTagsSimple "head" (inlinesToTEI opts title) $$ @@ -181,7 +181,7 @@ blockToTEI _ (CodeBlock (_,classes,_) str) = else languagesByExtension . map toLower $ s langs = concatMap langsFrom classes blockToTEI opts (BulletList lst) = - let attribs = [("type", "bullet") | isTightList lst] + let attribs = [("type", "unordered")] in inTags True "list" attribs $ listItemsToTEI opts lst blockToTEI _ (OrderedList _ []) = empty blockToTEI opts (OrderedList (start, numstyle, _) (first:rest)) = @@ -277,9 +277,9 @@ inlineToTEI _ (Math t str) = DisplayMath -> inTags True "figure" [("type","math")] $ inTags False "formula" [("notation","TeX")] $ text (str) -inlineToTEI _ (RawInline f x) | f == "html" || f == "tei" = text x - | otherwise = empty -inlineToTEI _ LineBreak = text "" +inlineToTEI _ (RawInline f x) | f == "tei" = text x + | otherwise = empty +inlineToTEI _ LineBreak = selfClosingTag "lb" [] inlineToTEI _ Space = space -- because we use \n for LineBreak, we can't do soft breaks: inlineToTEI _ SoftBreak = space diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs index 228cda67d..56764db9f 100644 --- a/tests/Tests/Writers/TEI.hs +++ b/tests/Tests/Writers/TEI.hs @@ -27,15 +27,17 @@ infix 4 =: tests :: [Test] tests = [ testGroup "block elements" ["para" =: para "Lorem ipsum cetera." - =?> "

Lorem ipsum cetera.

" + =?> "

Lorem ipsum cetera.

" ] --- ] --- , testGroup "lists" --- [ --- ] , testGroup "inlines" [ - "Emphasis" =: emph ("emphasized") - =?> "emphasized" - ] - ] + "Emphasis" =: emph ("emphasized") + =?> "

emphasized

" + ,"SingleQuoted" =: singleQuoted (text "quoted material") + =?> "

quoted material

" + ,"DoubleQuoted" =: doubleQuoted (text "quoted material") + =?> "

quoted material

" + ,"NestedQuoted" =: doubleQuoted (singleQuoted (text "quoted material")) + =?> "

quoted material

" + ] + ] -- cgit v1.2.3