diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-03-28 09:51:30 +0200 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-03-30 01:16:34 +0200 |
commit | 831e1c5edd4703b6ab0953a79980e37ea1bee5dc (patch) | |
tree | d718a4413706ac497d65fb7d5c709244096d2d3c | |
parent | 64fe39c255357c25fc636c46bc3bdfd31257b445 (diff) | |
download | pandoc-831e1c5edd4703b6ab0953a79980e37ea1bee5dc.tar.gz |
Added JATS writer.
* New module Text.Pandoc.Writer.JATS exporting writeJATS.
* New output format `jats`.
* Added tests.
* Revised manual.
-rw-r--r-- | MANUAL.txt | 12 | ||||
-rw-r--r-- | pandoc.cabal | 3 | ||||
-rw-r--r-- | src/Text/Pandoc.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/JATS.hs | 429 | ||||
-rw-r--r-- | test/Tests/Old.hs | 3 | ||||
-rw-r--r-- | test/tables.jats | 616 | ||||
-rw-r--r-- | test/writer.jats | 1425 |
7 files changed, 2485 insertions, 6 deletions
diff --git a/MANUAL.txt b/MANUAL.txt index e11e57459..f0e951f75 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -291,9 +291,9 @@ General options (LaTeX), `beamer` (LaTeX beamer slide show), `context` (ConTeXt), `man` (groff man), `mediawiki` (MediaWiki markup), `dokuwiki` (DokuWiki markup), `zimwiki` (ZimWiki markup), - `textile` (Textile), `org` (Emacs Org mode), - `texinfo` (GNU Texinfo), `opml` (OPML), `docbook` or `docbook4` - (DocBook 4), `docbook5` (DocBook 5), `opendocument` (OpenDocument), + `textile` (Textile), `org` (Emacs Org mode), `texinfo` (GNU Texinfo), + `opml` (OPML), `docbook` or `docbook4` (DocBook 4), `docbook5` + (DocBook 5), `jats` (JATS XML), `opendocument` (OpenDocument), `odt` (OpenOffice text document), `docx` (Word docx), `haddock` (Haddock markup), `rtf` (rich text format), `epub2` (EPUB v2 book), `epub` or `epub3` (EPUB v3), `fb2` (FictionBook2 e-book), @@ -616,8 +616,8 @@ General writer options : Include an automatically generated table of contents (or, in the case of `latex`, `context`, `docx`, `rst`, or `ms`, an instruction to create one) in the output document. This - option has no effect on `man`, `docbook4`, `docbook5`, `slidy`, - `slideous`, `s5`, or `odt` output. + option has no effect on `man`, `docbook4`, `docbook5`, `jats`, + `slidy`, `slideous`, `s5`, or `odt` output. `--toc-depth=`*NUMBER* @@ -1000,7 +1000,7 @@ Math rendering in HTML `--mathml` -: Convert TeX math to [MathML] (in `docbook4`, `docbook5`, +: Convert TeX math to [MathML] (in `docbook4`, `docbook5`, `jats`, `html4` and `html5`). `--jsmath`[`=`*URL*] diff --git a/pandoc.cabal b/pandoc.cabal index 596b52c44..33694dec0 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -159,6 +159,7 @@ Extra-Source-Files: test/tables.context test/tables.docbook4 test/tables.docbook5 + test/tables.jats test/tables.dokuwiki test/tables.zimwiki test/tables.icml @@ -187,6 +188,7 @@ Extra-Source-Files: test/writer.context test/writer.docbook4 test/writer.docbook5 + test/writer.jats test/writer.html4 test/writer.html5 test/writer.man @@ -381,6 +383,7 @@ Library Text.Pandoc.Readers.EPUB, Text.Pandoc.Writers.Native, Text.Pandoc.Writers.Docbook, + Text.Pandoc.Writers.JATS, Text.Pandoc.Writers.OPML, Text.Pandoc.Writers.HTML, Text.Pandoc.Writers.ICML, diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index e77bc6d45..977ad1ab4 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -117,6 +117,7 @@ module Text.Pandoc , writeICML , writeDocbook4 , writeDocbook5 + , writeJATS , writeOPML , writeOpenDocument , writeMan @@ -182,6 +183,7 @@ import Text.Pandoc.Writers.CommonMark import Text.Pandoc.Writers.ConTeXt import Text.Pandoc.Writers.Custom import Text.Pandoc.Writers.Docbook +import Text.Pandoc.Writers.JATS import Text.Pandoc.Writers.Docx import Text.Pandoc.Writers.DokuWiki import Text.Pandoc.Writers.EPUB @@ -287,6 +289,7 @@ writers = [ ,("docbook" , StringWriter writeDocbook5) ,("docbook4" , StringWriter writeDocbook4) ,("docbook5" , StringWriter writeDocbook5) + ,("jats" , StringWriter writeJATS) ,("opml" , StringWriter writeOPML) ,("opendocument" , StringWriter writeOpenDocument) ,("latex" , StringWriter writeLaTeX) diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs new file mode 100644 index 000000000..9aaba78e0 --- /dev/null +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -0,0 +1,429 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternGuards #-} +{- +Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu> + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} +{- | + Module : Text.Pandoc.Writers.JATS + Copyright : Copyright (C) 2017 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <jgm@berkeley.edu> + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' documents to JATS XML. +Reference: +https://jats.nlm.nih.gov/publishing/tag-library/1.1d3/element/mml-math.html +-} +module Text.Pandoc.Writers.JATS ( writeJATS ) where +import Control.Monad.Reader +import Data.Char (toLower) +import Data.Generics (everywhere, mkT) +import Data.List (intercalate, isSuffixOf) +import Data.Maybe (fromMaybe) +import qualified Text.Pandoc.Builder as B +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Definition +import Text.Pandoc.Highlighting (languages, languagesByExtension) +import Text.Pandoc.Logging +import Text.Pandoc.Options +import Text.Pandoc.Pretty +import Text.Pandoc.Shared +import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Writers.Math +import Text.Pandoc.Writers.Shared +import Text.Pandoc.XML +import Text.Pandoc.MIME (getMimeType) +import Text.TeXMath +import qualified Text.XML.Light as Xml + +data JATSVersion = JATS1_1 + deriving (Eq, Show) + +type DB = ReaderT JATSVersion + +-- | Convert list of authors to a docbook <author> section +authorToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m B.Inlines +authorToJATS opts name' = do + name <- render Nothing <$> inlinesToJATS opts name' + let colwidth = if writerWrapText opts == WrapAuto + then Just $ writerColumns opts + else Nothing + return $ B.rawInline "docbook" $ render colwidth $ + if ',' `elem` name + then -- last name first + let (lastname, rest) = break (==',') name + firstname = triml rest in + inTagsSimple "firstname" (text $ escapeStringForXML firstname) <> + inTagsSimple "surname" (text $ escapeStringForXML lastname) + else -- last name last + let namewords = words name + lengthname = length namewords + (firstname, lastname) = case lengthname of + 0 -> ("","") + 1 -> ("", name) + n -> (intercalate " " (take (n-1) namewords), last namewords) + in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$ + inTagsSimple "surname" (text $ escapeStringForXML lastname) + +writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m String +writeJATS opts d = + runReaderT (docToJATS opts d) JATS1_1 + +-- | Convert Pandoc document to string in JATS format. +docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> DB m String +docToJATS opts (Pandoc meta blocks) = do + let elements = hierarchicalize blocks + let colwidth = if writerWrapText opts == WrapAuto + then Just $ writerColumns opts + else Nothing + let render' = render colwidth + let opts' = if (maybe False (("/book>" `isSuffixOf`) . trimr) + (writerTemplate opts) && + TopLevelDefault == writerTopLevelDivision opts) + then opts{ writerTopLevelDivision = TopLevelChapter } + else opts + -- The numbering here follows LaTeX's internal numbering + let startLvl = case writerTopLevelDivision opts' of + TopLevelPart -> -1 + TopLevelChapter -> 0 + TopLevelSection -> 1 + TopLevelDefault -> 1 + auths' <- mapM (authorToJATS opts) $ docAuthors meta + let meta' = B.setMeta "author" auths' meta + metadata <- metaToJSON opts + (fmap (render colwidth . vcat) . + (mapM (elementToJATS opts' startLvl) . + hierarchicalize)) + (fmap (render colwidth) . inlinesToJATS opts') + meta' + main <- (render' . inTagsIndented "body" . vcat) <$> + (mapM (elementToJATS opts' startLvl) elements) + let context = defField "body" main + $ defField "mathml" (case writerHTMLMathMethod opts of + MathML -> True + _ -> False) + $ metadata + return $ case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate' tpl context + +-- | Convert an Element to JATS. +elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> DB m Doc +elementToJATS opts _ (Blk block) = blockToJATS opts block +elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do + let idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')] + let otherAttrs = ["sec-type", "specific-use"] + let attribs = idAttr ++ [(k,v) | (k,v) <- kvs, k `elem` otherAttrs] + contents <- mapM (elementToJATS opts (lvl + 1)) elements + title' <- inlinesToJATS opts title + return $ inTags True "sec" attribs $ + inTagsSimple "title" title' $$ vcat contents + +-- | Convert a list of Pandoc blocks to JATS. +blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> DB m Doc +blocksToJATS opts = fmap vcat . mapM (blockToJATS opts) + +-- | Auxiliary function to convert Plain block to Para. +plainToPara :: Block -> Block +plainToPara (Plain x) = Para x +plainToPara x = x + +-- | Convert a list of pairs of terms and definitions into a list of +-- JATS varlistentrys. +deflistItemsToJATS :: PandocMonad m + => WriterOptions -> [([Inline],[[Block]])] -> DB m Doc +deflistItemsToJATS opts items = + vcat <$> mapM (\(term, defs) -> deflistItemToJATS opts term defs) items + +-- | Convert a term and a list of blocks into a JATS varlistentry. +deflistItemToJATS :: PandocMonad m + => WriterOptions -> [Inline] -> [[Block]] -> DB m Doc +deflistItemToJATS opts term defs = do + term' <- inlinesToJATS opts term + def' <- blocksToJATS opts $ concatMap (map plainToPara) defs + return $ inTagsIndented "def-item" $ + inTagsIndented "term" term' $$ + inTagsIndented "def" def' + +-- | Convert a list of lists of blocks to a list of JATS list items. +listItemsToJATS :: PandocMonad m + => WriterOptions -> (Maybe [String]) -> [[Block]] -> DB m Doc +listItemsToJATS opts markers items = + case markers of + Nothing -> vcat <$> mapM (listItemToJATS opts Nothing) items + Just ms -> vcat <$> zipWithM (listItemToJATS opts) (map Just ms) items + +-- | Convert a list of blocks into a JATS list item. +listItemToJATS :: PandocMonad m + => WriterOptions -> (Maybe String) -> [Block] -> DB m Doc +listItemToJATS opts mbmarker item = do + contents <- blocksToJATS opts item + return $ inTagsIndented "list-item" $ + maybe empty (\lbl -> inTagsIndented "label" (text lbl)) mbmarker + $$ contents + +-- | Convert a Pandoc block element to JATS. +blockToJATS :: PandocMonad m => WriterOptions -> Block -> DB m Doc +blockToJATS _ Null = return empty +-- Add ids to paragraphs in divs with ids - this is needed for +-- pandoc-citeproc to get link anchors in bibliographies: +blockToJATS opts (Div (ident,_,_) [Para lst]) = + let attribs = [("id", ident) | not (null ident)] in + inTags True "p" attribs <$> inlinesToJATS opts lst +blockToJATS opts (Div (ident,_,kvs) bs) = do + contents <- blocksToJATS opts bs + let attr = [("id", ident) | not (null ident)] ++ + [("xml:lang",l) | ("lang",l) <- kvs] ++ + [(k,v) | (k,v) <- kvs, k `elem` ["specific-use", + "content-type", "orientation", "position"]] + return $ inTags True "boxed-text" attr contents +blockToJATS _ (Header _ _ _) = + return empty -- should not occur after hierarchicalize +-- No Plain, everything needs to be in a block-level tag +blockToJATS opts (Plain lst) = blockToJATS opts (Para lst) +-- title beginning with fig: indicates that the image is a figure +blockToJATS opts (Para [Image (ident,_,kvs) txt + (src,'f':'i':'g':':':tit)]) = do + alt <- inlinesToJATS opts txt + let capt = if null txt + then empty + else inTagsSimple "caption" alt + let attr = [("id", ident) | not (null ident)] ++ + [(k,v) | (k,v) <- kvs, k `elem` ["fig-type", "orientation", + "position", "specific-use"]] + let mbMT = getMimeType src + let maintype = fromMaybe "image" $ + lookup "mimetype" kvs `mplus` + (takeWhile (/='/') <$> mbMT) + let subtype = fromMaybe "" $ + lookup "mime-subtype" kvs `mplus` + ((drop 1 . dropWhile (/='/')) <$> mbMT) + let graphicattr = [("mimetype",maintype), + ("mime-subtype",drop 1 subtype), + ("xlink:href",src), -- do we need to URL escape this? + ("xlink:title",tit)] + return $ inTags True "fig" attr $ + capt $$ selfClosingTag "graphic" graphicattr +blockToJATS opts (Para lst) = + inTagsIndented "p" <$> inlinesToJATS opts lst +blockToJATS opts (LineBlock lns) = + blockToJATS opts $ linesToPara lns +blockToJATS opts (BlockQuote blocks) = + inTagsIndented "disp-quote" <$> blocksToJATS opts blocks +blockToJATS _ (CodeBlock (ident,classes,kvs) str) = return $ + inTags False tag attr (flush (text (escapeStringForXML str))) + where attr = [("id",ident) | not (null ident)] ++ + [("language",lang) | not (null lang)] ++ + [(k,v) | (k,v) <- kvs, k `elem` ["code-type", + "code-version", "executable", + "language-version", "orientation", + "platforms", "position", "specific-use"]] + tag = if null lang then "preformat" else "code" + lang = case langs of + (l:_) -> escapeStringForXML l + [] -> "" + isLang l = map toLower l `elem` map (map toLower) languages + langsFrom s = if isLang s + then [s] + else languagesByExtension . map toLower $ s + langs = concatMap langsFrom classes +blockToJATS _ (BulletList []) = return empty +blockToJATS opts (BulletList lst) = do + inTags True "list" [("list-type", "bullet")] <$> + listItemsToJATS opts Nothing lst +blockToJATS _ (OrderedList _ []) = return empty +blockToJATS opts (OrderedList (start, numstyle, delimstyle) items) = do + let listType = case numstyle of + DefaultStyle -> "order" + Decimal -> "order" + Example -> "order" + UpperAlpha -> "alpha-upper" + LowerAlpha -> "alpha-lower" + UpperRoman -> "roman-upper" + LowerRoman -> "roman-lower" + let simpleList = start == 1 && (delimstyle == DefaultDelim || + delimstyle == Period) + let markers = if simpleList + then Nothing + else Just $ + orderedListMarkers (start, numstyle, delimstyle) + inTags True "list" [("list-type", listType)] <$> + listItemsToJATS opts markers items +blockToJATS opts (DefinitionList lst) = do + inTags True "def-list" [] <$> deflistItemsToJATS opts lst +blockToJATS _ b@(RawBlock f str) + | f == "jats" = return $ text str -- raw XML block + | otherwise = do + report $ BlockNotRendered b + return empty +blockToJATS _ HorizontalRule = return empty -- not semantic +blockToJATS opts (Table [] aligns widths headers rows) = do + let percent w = show (truncate (100*w) :: Integer) ++ "*" + let coltags = vcat $ zipWith (\w al -> selfClosingTag "col" + ([("width", percent w) | w > 0] ++ + [("align", alignmentToString al)])) widths aligns + thead <- if all null headers + then return empty + else inTagsIndented "thead" <$> tableRowToJATS opts True headers + tbody <- (inTagsIndented "tbody" . vcat) <$> + mapM (tableRowToJATS opts False) rows + return $ inTags True "table" [] $ coltags $$ thead $$ tbody +blockToJATS opts (Table caption aligns widths headers rows) = do + captionDoc <- inTagsIndented "caption" <$> blockToJATS opts (Para caption) + tbl <- blockToJATS opts (Table [] aligns widths headers rows) + return $ inTags True "table-wrap" [] $ captionDoc $$ tbl + +alignmentToString :: Alignment -> [Char] +alignmentToString alignment = case alignment of + AlignLeft -> "left" + AlignRight -> "right" + AlignCenter -> "center" + AlignDefault -> "left" + +tableRowToJATS :: PandocMonad m + => WriterOptions + -> Bool + -> [[Block]] + -> DB m Doc +tableRowToJATS opts isHeader cols = + (inTagsIndented "tr" . vcat) <$> mapM (tableItemToJATS opts isHeader) cols + +tableItemToJATS :: PandocMonad m + => WriterOptions + -> Bool + -> [Block] + -> DB m Doc +tableItemToJATS opts isHeader item = + (inTags True (if isHeader then "th" else "td") [] . vcat) <$> + mapM (blockToJATS opts) item + +-- | Convert a list of inline elements to JATS. +inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m Doc +inlinesToJATS opts lst = hcat <$> mapM (inlineToJATS opts) lst + +-- | Convert an inline element to JATS. +inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> DB m Doc +inlineToJATS _ (Str str) = return $ text $ escapeStringForXML str +inlineToJATS opts (Emph lst) = + inTagsSimple "italic" <$> inlinesToJATS opts lst +inlineToJATS opts (Strong lst) = + inTags False "bold" [("role", "strong")] <$> inlinesToJATS opts lst +inlineToJATS opts (Strikeout lst) = + inTagsSimple "strike" <$> inlinesToJATS opts lst +inlineToJATS opts (Superscript lst) = + inTagsSimple "sup" <$> inlinesToJATS opts lst +inlineToJATS opts (Subscript lst) = + inTagsSimple "sub" <$> inlinesToJATS opts lst +inlineToJATS opts (SmallCaps lst) = + inTags False "sc" [("role", "smallcaps")] <$> + inlinesToJATS opts lst +inlineToJATS opts (Quoted SingleQuote lst) = do + contents <- inlinesToJATS opts lst + return $ char '‘' <> contents <> char '’' +inlineToJATS opts (Quoted DoubleQuote lst) = do + contents <- inlinesToJATS opts lst + return $ char '“' <> contents <> char '”' +inlineToJATS _ (Code _ str) = + return $ inTagsSimple "monospace" $ text (escapeStringForXML str) +inlineToJATS _ il@(RawInline f x) + | f == "jats" = return $ text x + | otherwise = do + report $ InlineNotRendered il + return empty +inlineToJATS _ LineBreak = return $ selfClosingTag "break" [] +inlineToJATS _ Space = return space +inlineToJATS opts SoftBreak + | writerWrapText opts == WrapPreserve = return cr + | otherwise = return space +inlineToJATS opts (Note contents) = + -- TODO technically only <p> tags are allowed inside + inTagsIndented "fn" <$> blocksToJATS opts contents +inlineToJATS opts (Cite _ lst) = + -- TODO revisit this after examining the jats.csl pipeline + inlinesToJATS opts lst +inlineToJATS opts (Span ("",_,[]) ils) = inlinesToJATS opts ils +inlineToJATS opts (Span (ident,_,kvs) ils) = do + contents <- inlinesToJATS opts ils + let attr = [("id",ident) | not (null ident)] ++ + [("xml:lang",l) | ("lang",l) <- kvs] ++ + [(k,v) | (k,v) <- kvs + , k `elem` ["content-type", "rationale", + "rid", "specific-use"]] + return $ selfClosingTag "milestone-start" attr <> contents <> + selfClosingTag "milestone-end" [] +inlineToJATS _ (Math t str) = do + let addPref (Xml.Attr q v) + | Xml.qName q == "xmlns" = Xml.Attr q{ Xml.qName = "xmlns:mml" } v + | otherwise = Xml.Attr q v + let fixNS' e = e{ Xml.elName = + (Xml.elName e){ Xml.qPrefix = Just "mml" } } + let fixNS = everywhere (mkT fixNS') . + (\e -> e{ Xml.elAttribs = map addPref (Xml.elAttribs e) }) + let conf = Xml.useShortEmptyTags (const False) Xml.defaultConfigPP + res <- convertMath writeMathML t str + let tagtype = case t of + DisplayMath -> "disp-formula" + InlineMath -> "inline-formula" + return $ inTagsSimple tagtype $ + case res of + Right r -> text $ Xml.ppcElement conf + $ fixNS r + Left _ -> inTagsSimple "tex-math" + $ text "<![CDATA[" <> + text str <> + text "]]>" +inlineToJATS _ (Link _attr [Str t] ('m':'a':'i':'l':'t':'o':':':email, _)) + | escapeURI t == email = + return $ inTagsSimple "email" $ text (escapeStringForXML email) +inlineToJATS opts (Link (ident,_,kvs) txt ('#':src, _)) = do + let attr = [("id", ident) | not (null ident)] ++ + [("alt", stringify txt), + ("rid", src)] ++ + [(k,v) | (k,v) <- kvs, k `elem` ["ref-type", "specific-use"]] + contents <- inlinesToJATS opts txt + return $ inTags False "xref" attr contents +inlineToJATS opts (Link (ident,_,kvs) txt (src, tit)) = do + let attr = [("id", ident) | not (null ident)] ++ + [("ext-link-type", "uri"), + ("xlink:href", src)] ++ + [("xlink:title", tit) | not (null tit)] ++ + [(k,v) | (k,v) <- kvs, k `elem` ["assigning-authority", + "specific-use", "xlink:actuate", + "xlink:role", "xlink:show", + "xlink:type"]] + contents <- inlinesToJATS opts txt + return $ inTags False "ext-link" attr contents +inlineToJATS _ (Image (ident,_,kvs) _ (src, tit)) = do + let mbMT = getMimeType src + let maintype = fromMaybe "image" $ + lookup "mimetype" kvs `mplus` + (takeWhile (/='/') <$> mbMT) + let subtype = fromMaybe "" $ + lookup "mime-subtype" kvs `mplus` + ((drop 1 . dropWhile (/='/')) <$> mbMT) + let attr = [("id", ident) | not (null ident)] ++ + [("mimetype", maintype), + ("mime-subtype", subtype), + ("xlink:href", src)] ++ + [("xlink:title", tit) | not (null tit)] ++ + [(k,v) | (k,v) <- kvs, k `elem` ["baseline-shift", + "content-type", "specific-use", "xlink:actuate", + "xlink:href", "xlink:role", "xlink:show", + "xlink:type"]] + return $ selfClosingTag "inline-graphic" attr diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index 3c473792f..fceb776f7 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -77,6 +77,9 @@ tests = [ testGroup "markdown" , testGroup "docbook5" [ testGroup "writer" $ writerTests "docbook5" ] + , testGroup "jats" + [ testGroup "writer" $ writerTests "jats" + ] , testGroup "native" [ testGroup "writer" $ writerTests "native" , test "reader" ["-r", "native", "-w", "native", "-s"] diff --git a/test/tables.jats b/test/tables.jats new file mode 100644 index 000000000..11f543f17 --- /dev/null +++ b/test/tables.jats @@ -0,0 +1,616 @@ +<body> + <p> + Simple table with caption: + </p> + <table-wrap> + <caption> + <p> + Demonstration of simple table syntax. + </p> + </caption> + <table> + <col align="right" /> + <col align="left" /> + <col align="center" /> + <col align="left" /> + <thead> + <tr> + <th> + <p> + Right + </p> + </th> + <th> + <p> + Left + </p> + </th> + <th> + <p> + Center + </p> + </th> + <th> + <p> + Default + </p> + </th> + </tr> + </thead> + <tbody> + <tr> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + </tr> + <tr> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + </tr> + <tr> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + </tr> + </tbody> + </table> + </table-wrap> + <p> + Simple table without caption: + </p> + <table> + <col align="right" /> + <col align="left" /> + <col align="center" /> + <col align="left" /> + <thead> + <tr> + <th> + <p> + Right + </p> + </th> + <th> + <p> + Left + </p> + </th> + <th> + <p> + Center + </p> + </th> + <th> + <p> + Default + </p> + </th> + </tr> + </thead> + <tbody> + <tr> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + </tr> + <tr> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + </tr> + <tr> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + </tr> + </tbody> + </table> + <p> + Simple table indented two spaces: + </p> + <table-wrap> + <caption> + <p> + Demonstration of simple table syntax. + </p> + </caption> + <table> + <col align="right" /> + <col align="left" /> + <col align="center" /> + <col align="left" /> + <thead> + <tr> + <th> + <p> + Right + </p> + </th> + <th> + <p> + Left + </p> + </th> + <th> + <p> + Center + </p> + </th> + <th> + <p> + Default + </p> + </th> + </tr> + </thead> + <tbody> + <tr> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + </tr> + <tr> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + </tr> + <tr> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + </tr> + </tbody> + </table> + </table-wrap> + <p> + Multiline table with caption: + </p> + <table-wrap> + <caption> + <p> + Here’s the caption. It may span multiple lines. + </p> + </caption> + <table> + <col width="15*" align="center" /> + <col width="13*" align="left" /> + <col width="16*" align="right" /> + <col width="33*" align="left" /> + <thead> + <tr> + <th> + <p> + Centered Header + </p> + </th> + <th> + <p> + Left Aligned + </p> + </th> + <th> + <p> + Right Aligned + </p> + </th> + <th> + <p> + Default aligned + </p> + </th> + </tr> + </thead> + <tbody> + <tr> + <td> + <p> + First + </p> + </td> + <td> + <p> + row + </p> + </td> + <td> + <p> + 12.0 + </p> + </td> + <td> + <p> + Example of a row that spans multiple lines. + </p> + </td> + </tr> + <tr> + <td> + <p> + Second + </p> + </td> + <td> + <p> + row + </p> + </td> + <td> + <p> + 5.0 + </p> + </td> + <td> + <p> + Here’s another one. Note the blank line between rows. + </p> + </td> + </tr> + </tbody> + </table> + </table-wrap> + <p> + Multiline table without caption: + </p> + <table> + <col width="15*" align="center" /> + <col width="13*" align="left" /> + <col width="16*" align="right" /> + <col width="33*" align="left" /> + <thead> + <tr> + <th> + <p> + Centered Header + </p> + </th> + <th> + <p> + Left Aligned + </p> + </th> + <th> + <p> + Right Aligned + </p> + </th> + <th> + <p> + Default aligned + </p> + </th> + </tr> + </thead> + <tbody> + <tr> + <td> + <p> + First + </p> + </td> + <td> + <p> + row + </p> + </td> + <td> + <p> + 12.0 + </p> + </td> + <td> + <p> + Example of a row that spans multiple lines. + </p> + </td> + </tr> + <tr> + <td> + <p> + Second + </p> + </td> + <td> + <p> + row + </p> + </td> + <td> + <p> + 5.0 + </p> + </td> + <td> + <p> + Here’s another one. Note the blank line between rows. + </p> + </td> + </tr> + </tbody> + </table> + <p> + Table without column headers: + </p> + <table> + <col align="right" /> + <col align="left" /> + <col align="center" /> + <col align="right" /> + <tbody> + <tr> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + <td> + <p> + 12 + </p> + </td> + </tr> + <tr> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + <td> + <p> + 123 + </p> + </td> + </tr> + <tr> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + <td> + <p> + 1 + </p> + </td> + </tr> + </tbody> + </table> + <p> + Multiline table without column headers: + </p> + <table> + <col width="15*" align="center" /> + <col width="13*" align="left" /> + <col width="16*" align="right" /> + <col width="33*" align="left" /> + <tbody> + <tr> + <td> + <p> + First + </p> + </td> + <td> + <p> + row + </p> + </td> + <td> + <p> + 12.0 + </p> + </td> + <td> + <p> + Example of a row that spans multiple lines. + </p> + </td> + </tr> + <tr> + <td> + <p> + Second + </p> + </td> + <td> + <p> + row + </p> + </td> + <td> + <p> + 5.0 + </p> + </td> + <td> + <p> + Here’s another one. Note the blank line between rows. + </p> + </td> + </tr> + </tbody> + </table> +</body> diff --git a/test/writer.jats b/test/writer.jats new file mode 100644 index 000000000..1703de4aa --- /dev/null +++ b/test/writer.jats @@ -0,0 +1,1425 @@ +<?xml version="1.0" encoding="utf-8" ?> +<!DOCTYPE article PUBLIC "-//NLM//DTD JATS (Z39.96) Journal Publishing DTD v1.0 20120330//EN" + "JATS-journalpublishing1.dtd"> +<article xmlns:mml="http://www.w3.org/1998/Math/MathML" xmlns:xlink="http://www.w3.org/1999/xlink" dtd-version="1.0" article-type="other"> +<front> +<journal-meta> +<journal-title-group> +</journal-title-group> +<publisher> +<publisher-name></publisher-name> +</publisher> +</journal-meta> +<article-meta> +<title-group> +<article-title>Pandoc Test Suite</article-title> +</title-group> +<pub-date pub-type="epub"> +<string-date>July 17, 2006</string-date> +</pub-date> +</article-meta> +</front> +<body> + <p> + This is a set of tests for pandoc. Most of them are adapted from John + Gruber’s markdown test suite. + </p> + <sec id="headers"> + <title>Headers</title> + <sec id="level-2-with-an-embedded-link"> + <title>Level 2 with an + <ext-link ext-link-type="uri" xlink:href="/url">embedded + link</ext-link></title> + <sec id="level-3-with-emphasis"> + <title>Level 3 with <italic>emphasis</italic></title> + <sec id="level-4"> + <title>Level 4</title> + <sec id="level-5"> + <title>Level 5</title> + </sec> + </sec> + </sec> + </sec> + </sec> + <sec id="level-1"> + <title>Level 1</title> + <sec id="level-2-with-emphasis"> + <title>Level 2 with <italic>emphasis</italic></title> + <sec id="level-3"> + <title>Level 3</title> + <p> + with no blank line + </p> + </sec> + </sec> + <sec id="level-2"> + <title>Level 2</title> + <p> + with no blank line + </p> + </sec> + </sec> + <sec id="paragraphs"> + <title>Paragraphs</title> + <p> + Here’s a regular paragraph. + </p> + <p> + In Markdown 1.0.0 and earlier. Version 8. This line turns into a list + item. Because a hard-wrapped line in the middle of a paragraph looked + like a list item. + </p> + <p> + Here’s one with a bullet. * criminey. + </p> + <p> + There should be a hard line break<break />here. + </p> + </sec> + <sec id="block-quotes"> + <title>Block Quotes</title> + <p> + E-mail style: + </p> + <disp-quote> + <p> + This is a block quote. It is pretty short. + </p> + </disp-quote> + <disp-quote> + <p> + Code in a block quote: + </p> + <preformat>sub status { + print "working"; +}</preformat> + <p> + A list: + </p> + <list list-type="order"> + <list-item> + <p> + item one + </p> + </list-item> + <list-item> + <p> + item two + </p> + </list-item> + </list> + <p> + Nested block quotes: + </p> + <disp-quote> + <p> + nested + </p> + </disp-quote> + <disp-quote> + <p> + nested + </p> + </disp-quote> + </disp-quote> + <p> + This should not be a block quote: 2 > 1. + </p> + <p> + And a following paragraph. + </p> + </sec> + <sec id="code-blocks"> + <title>Code Blocks</title> + <p> + Code: + </p> + <preformat>---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab</preformat> + <p> + And: + </p> + <preformat> this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{</preformat> + </sec> + <sec id="lists"> + <title>Lists</title> + <sec id="unordered"> + <title>Unordered</title> + <p> + Asterisks tight: + </p> + <list list-type="bullet"> + <list-item> + <p> + asterisk 1 + </p> + </list-item> + <list-item> + <p> + asterisk 2 + </p> + </list-item> + <list-item> + <p> + asterisk 3 + </p> + </list-item> + </list> + <p> + Asterisks loose: + </p> + <list list-type="bullet"> + <list-item> + <p> + asterisk 1 + </p> + </list-item> + <list-item> + <p> + asterisk 2 + </p> + </list-item> + <list-item> + <p> + asterisk 3 + </p> + </list-item> + </list> + <p> + Pluses tight: + </p> + <list list-type="bullet"> + <list-item> + <p> + Plus 1 + </p> + </list-item> + <list-item> + <p> + Plus 2 + </p> + </list-item> + <list-item> + <p> + Plus 3 + </p> + </list-item> + </list> + <p> + Pluses loose: + </p> + <list list-type="bullet"> + <list-item> + <p> + Plus 1 + </p> + </list-item> + <list-item> + <p> + Plus 2 + </p> + </list-item> + <list-item> + <p> + Plus 3 + </p> + </list-item> + </list> + <p> + Minuses tight: + </p> + <list list-type="bullet"> + <list-item> + <p> + Minus 1 + </p> + </list-item> + <list-item> + <p> + Minus 2 + </p> + </list-item> + <list-item> + <p> + Minus 3 + </p> + </list-item> + </list> + <p> + Minuses loose: + </p> + <list list-type="bullet"> + <list-item> + <p> + Minus 1 + </p> + </list-item> + <list-item> + <p> + Minus 2 + </p> + </list-item> + <list-item> + <p> + Minus 3 + </p> + </list-item> + </list> + </sec> + <sec id="ordered"> + <title>Ordered</title> + <p> + Tight: + </p> + <list list-type="order"> + <list-item> + <p> + First + </p> + </list-item> + <list-item> + <p> + Second + </p> + </list-item> + <list-item> + <p> + Third + </p> + </list-item> + </list> + <p> + and: + </p> + <list list-type="order"> + <list-item> + <p> + One + </p> + </list-item> + <list-item> + <p> + Two + </p> + </list-item> + <list-item> + <p> + Three + </p> + </list-item> + </list> + <p> + Loose using tabs: + </p> + <list list-type="order"> + <list-item> + <p> + First + </p> + </list-item> + <list-item> + <p> + Second + </p> + </list-item> + <list-item> + <p> + Third + </p> + </list-item> + </list> + <p> + and using spaces: + </p> + <list list-type="order"> + <list-item> + <p> + One + </p> + </list-item> + <list-item> + <p> + Two + </p> + </list-item> + <list-item> + <p> + Three + </p> + </list-item> + </list> + <p> + Multiple paragraphs: + </p> + <list list-type="order"> + <list-item> + <p> + Item 1, graf one. + </p> + <p> + Item 1. graf two. The quick brown fox jumped over the lazy dog’s + back. + </p> + </list-item> + <list-item> + <p> + Item 2. + </p> + </list-item> + <list-item> + <p> + Item 3. + </p> + </list-item> + </list> + </sec> + <sec id="nested"> + <title>Nested</title> + <list list-type="bullet"> + <list-item> + <p> + Tab + </p> + <list list-type="bullet"> + <list-item> + <p> + Tab + </p> + <list list-type="bullet"> + <list-item> + <p> + Tab + </p> + </list-item> + </list> + </list-item> + </list> + </list-item> + </list> + <p> + Here’s another: + </p> + <list list-type="order"> + <list-item> + <p> + First + </p> + </list-item> + <list-item> + <p> + Second: + </p> + <list list-type="bullet"> + <list-item> + <p> + Fee + </p> + </list-item> + <list-item> + <p> + Fie + </p> + </list-item> + <list-item> + <p> + Foe + </p> + </list-item> + </list> + </list-item> + <list-item> + <p> + Third + </p> + </list-item> + </list> + <p> + Same thing but with paragraphs: + </p> + <list list-type="order"> + <list-item> + <p> + First + </p> + </list-item> + <list-item> + <p> + Second: + </p> + <list list-type="bullet"> + <list-item> + <p> + Fee + </p> + </list-item> + <list-item> + <p> + Fie + </p> + </list-item> + <list-item> + <p> + Foe + </p> + </list-item> + </list> + </list-item> + <list-item> + <p> + Third + </p> + </list-item> + </list> + </sec> + <sec id="tabs-and-spaces"> + <title>Tabs and spaces</title> + <list list-type="bullet"> + <list-item> + <p> + this is a list item indented with tabs + </p> + </list-item> + <list-item> + <p> + this is a list item indented with spaces + </p> + <list list-type="bullet"> + <list-item> + <p> + this is an example list item indented with tabs + </p> + </list-item> + <list-item> + <p> + this is an example list item indented with spaces + </p> + </list-item> + </list> + </list-item> + </list> + </sec> + <sec id="fancy-list-markers"> + <title>Fancy list markers</title> + <list list-type="order"> + <list-item> + <label> + (2) + </label> + <p> + begins with 2 + </p> + </list-item> + <list-item> + <label> + (3) + </label> + <p> + and now 3 + </p> + <p> + with a continuation + </p> + <list list-type="roman-lower"> + <list-item> + <label> + iv. + </label> + <p> + sublist with roman numerals, starting with 4 + </p> + </list-item> + <list-item> + <label> + v. + </label> + <p> + more items + </p> + <list list-type="alpha-upper"> + <list-item> + <label> + (A) + </label> + <p> + a subsublist + </p> + </list-item> + <list-item> + <label> + (B) + </label> + <p> + a subsublist + </p> + </list-item> + </list> + </list-item> + </list> + </list-item> + </list> + <p> + Nesting: + </p> + <list list-type="alpha-upper"> + <list-item> + <p> + Upper Alpha + </p> + <list list-type="roman-upper"> + <list-item> + <p> + Upper Roman. + </p> + <list list-type="order"> + <list-item> + <label> + (6) + </label> + <p> + Decimal start with 6 + </p> + <list list-type="alpha-lower"> + <list-item> + <label> + c) + </label> + <p> + Lower alpha with paren + </p> + </list-item> + </list> + </list-item> + </list> + </list-item> + </list> + </list-item> + </list> + <p> + Autonumbering: + </p> + <list list-type="order"> + <list-item> + <p> + Autonumber. + </p> + </list-item> + <list-item> + <p> + More. + </p> + <list list-type="order"> + <list-item> + <p> + Nested. + </p> + </list-item> + </list> + </list-item> + </list> + <p> + Should not be a list item: + </p> + <p> + M.A. 2007 + </p> + <p> + B. Williams + </p> + </sec> + </sec> + <sec id="definition-lists"> + <title>Definition Lists</title> + <p> + Tight using spaces: + </p> + <def-list> + <def-item> + <term> + apple + </term> + <def> + <p> + red fruit + </p> + </def> + </def-item> + <def-item> + <term> + orange + </term> + <def> + <p> + orange fruit + </p> + </def> + </def-item> + <def-item> + <term> + banana + </term> + <def> + <p> + yellow fruit + </p> + </def> + </def-item> + </def-list> + <p> + Tight using tabs: + </p> + <def-list> + <def-item> + <term> + apple + </term> + <def> + <p> + red fruit + </p> + </def> + </def-item> + <def-item> + <term> + orange + </term> + <def> + <p> + orange fruit + </p> + </def> + </def-item> + <def-item> + <term> + banana + </term> + <def> + <p> + yellow fruit + </p> + </def> + </def-item> + </def-list> + <p> + Loose: + </p> + <def-list> + <def-item> + <term> + apple + </term> + <def> + <p> + red fruit + </p> + </def> + </def-item> + <def-item> + <term> + orange + </term> + <def> + <p> + orange fruit + </p> + </def> + </def-item> + <def-item> + <term> + banana + </term> + <def> + <p> + yellow fruit + </p> + </def> + </def-item> + </def-list> + <p> + Multiple blocks with italics: + </p> + <def-list> + <def-item> + <term> + <italic>apple</italic> + </term> + <def> + <p> + red fruit + </p> + <p> + contains seeds, crisp, pleasant to taste + </p> + </def> + </def-item> + <def-item> + <term> + <italic>orange</italic> + </term> + <def> + <p> + orange fruit + </p> + <preformat>{ orange code block }</preformat> + <disp-quote> + <p> + orange block quote + </p> + </disp-quote> + </def> + </def-item> + </def-list> + <p> + Multiple definitions, tight: + </p> + <def-list> + <def-item> + <term> + apple + </term> + <def> + <p> + red fruit + </p> + <p> + computer + </p> + </def> + </def-item> + <def-item> + <term> + orange + </term> + <def> + <p> + orange fruit + </p> + <p> + bank + </p> + </def> + </def-item> + </def-list> + <p> + Multiple definitions, loose: + </p> + <def-list> + <def-item> + <term> + apple + </term> + <def> + <p> + red fruit + </p> + <p> + computer + </p> + </def> + </def-item> + <def-item> + <term> + orange + </term> + <def> + <p> + orange fruit + </p> + <p> + bank + </p> + </def> + </def-item> + </def-list> + <p> + Blank line after term, indented marker, alternate markers: + </p> + <def-list> + <def-item> + <term> + apple + </term> + <def> + <p> + red fruit + </p> + <p> + computer + </p> + </def> + </def-item> + <def-item> + <term> + orange + </term> + <def> + <p> + orange fruit + </p> + <list list-type="order"> + <list-item> + <p> + sublist + </p> + </list-item> + <list-item> + <p> + sublist + </p> + </list-item> + </list> + </def> + </def-item> + </def-list> + </sec> + <sec id="html-blocks"> + <title>HTML Blocks</title> + <p> + Simple block on one line: + </p> + <boxed-text> + <p> + foo + </p> + </boxed-text> + <p> + And nested without indentation: + </p> + <boxed-text> + <boxed-text> + <p> + foo + </p> + </boxed-text> + <boxed-text> + <p> + bar + </p> + </boxed-text> + </boxed-text> + <p> + Interpreted markdown in a table: + </p> + <p> + This is <italic>emphasized</italic> + </p> + <p> + And this is <bold role="strong">strong</bold> + </p> + <p> + Here’s a simple block: + </p> + <p> + foo + </p> + <p> + This should be a code block, though: + </p> + <preformat><div> + foo +</div></preformat> + <p> + As should this: + </p> + <preformat><div>foo</div></preformat> + <p> + Now, nested: + </p> + <boxed-text> + <boxed-text> + <boxed-text> + <p> + foo + </p> + </boxed-text> + </boxed-text> + </boxed-text> + <p> + This should just be an HTML comment: + </p> + <p> + Multiline: + </p> + <p> + Code block: + </p> + <preformat><!-- Comment --></preformat> + <p> + Just plain comment, with trailing spaces on the line: + </p> + <p> + Code: + </p> + <preformat><hr /></preformat> + <p> + Hr’s: + </p> + </sec> + <sec id="inline-markup"> + <title>Inline Markup</title> + <p> + This is <italic>emphasized</italic>, and so <italic>is this</italic>. + </p> + <p> + This is <bold role="strong">strong</bold>, and so <bold role="strong">is + this</bold>. + </p> + <p> + An <italic><ext-link ext-link-type="uri" xlink:href="/url">emphasized + link</ext-link></italic>. + </p> + <p> + <bold role="strong"><italic>This is strong and em.</italic></bold> + </p> + <p> + So is <bold role="strong"><italic>this</italic></bold> word. + </p> + <p> + <bold role="strong"><italic>This is strong and em.</italic></bold> + </p> + <p> + So is <bold role="strong"><italic>this</italic></bold> word. + </p> + <p> + This is code: <monospace>></monospace>, <monospace>$</monospace>, + <monospace>\</monospace>, <monospace>\$</monospace>, + <monospace><html></monospace>. + </p> + <p> + <strike>This is <italic>strikeout</italic>.</strike> + </p> + <p> + Superscripts: a<sup>bc</sup>d a<sup><italic>hello</italic></sup> + a<sup>hello there</sup>. + </p> + <p> + Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O. + </p> + <p> + These should not be superscripts or subscripts, because of the unescaped + spaces: a^b c^d, a~b c~d. + </p> + </sec> + <sec id="smart-quotes-ellipses-dashes"> + <title>Smart quotes, ellipses, dashes</title> + <p> + “Hello,” said the spider. “‘Shelob’ is my name.” + </p> + <p> + ‘A’, ‘B’, and ‘C’ are letters. + </p> + <p> + ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ + </p> + <p> + ‘He said, “I want to go.”’ Were you alive in the 70’s? + </p> + <p> + Here is some quoted ‘<monospace>code</monospace>’ and a + “<ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&bar=2">quoted + link</ext-link>”. + </p> + <p> + Some dashes: one—two — three—four — five. + </p> + <p> + Dashes between numbers: 5–7, 255–66, 1987–1999. + </p> + <p> + Ellipses…and…and…. + </p> + </sec> + <sec id="latex"> + <title>LaTeX</title> + <list list-type="bullet"> + <list-item> + <p> + </p> + </list-item> + <list-item> + <p> + <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mn>2</mml:mn><mml:mo>+</mml:mo><mml:mn>2</mml:mn><mml:mo>=</mml:mo><mml:mn>4</mml:mn></mml:mrow></mml:math></inline-formula> + </p> + </list-item> + <list-item> + <p> + <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>x</mml:mi><mml:mo>∈</mml:mo><mml:mi>y</mml:mi></mml:mrow></mml:math></inline-formula> + </p> + </list-item> + <list-item> + <p> + <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>α</mml:mi><mml:mo>∧</mml:mo><mml:mi>ω</mml:mi></mml:mrow></mml:math></inline-formula> + </p> + </list-item> + <list-item> + <p> + <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mn>223</mml:mn></mml:math></inline-formula> + </p> + </list-item> + <list-item> + <p> + <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mi>p</mml:mi></mml:math></inline-formula>-Tree + </p> + </list-item> + <list-item> + <p> + Here’s some display math: + <disp-formula><mml:math display="block" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mfrac><mml:mi>d</mml:mi><mml:mrow><mml:mi>d</mml:mi><mml:mi>x</mml:mi></mml:mrow></mml:mfrac><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo><mml:mo>=</mml:mo><mml:munder><mml:mo>lim</mml:mo><mml:mrow><mml:mi>h</mml:mi><mml:mo accent="false">→</mml:mo><mml:mn>0</mml:mn></mml:mrow></mml:munder><mml:mfrac><mml:mrow><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo>+</mml:mo><mml:mi>h</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo><mml:mo>−</mml:mo><mml:mi>f</mml:mi><mml:mo stretchy="false" form="prefix">(</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy="false" form="postfix">)</mml:mo></mml:mrow><mml:mi>h</mml:mi></mml:mfrac></mml:mrow></mml:math></disp-formula> + </p> + </list-item> + <list-item> + <p> + Here’s one that has a line break in it: + <inline-formula><mml:math display="inline" xmlns:mml="http://www.w3.org/1998/Math/MathML"><mml:mrow><mml:mi>α</mml:mi><mml:mo>+</mml:mo><mml:mi>ω</mml:mi><mml:mo>×</mml:mo><mml:msup><mml:mi>x</mml:mi><mml:mn>2</mml:mn></mml:msup></mml:mrow></mml:math></inline-formula>. + </p> + </list-item> + </list> + <p> + These shouldn’t be math: + </p> + <list list-type="bullet"> + <list-item> + <p> + To get the famous equation, write <monospace>$e = mc^2$</monospace>. + </p> + </list-item> + <list-item> + <p> + $22,000 is a <italic>lot</italic> of money. So is $34,000. (It + worked if “lot” is emphasized.) + </p> + </list-item> + <list-item> + <p> + Shoes ($20) and socks ($5). + </p> + </list-item> + <list-item> + <p> + Escaped <monospace>$</monospace>: $73 <italic>this should be + emphasized</italic> 23$. + </p> + </list-item> + </list> + <p> + Here’s a LaTeX table: + </p> + </sec> + <sec id="special-characters"> + <title>Special Characters</title> + <p> + Here is some unicode: + </p> + <list list-type="bullet"> + <list-item> + <p> + I hat: Î + </p> + </list-item> + <list-item> + <p> + o umlaut: ö + </p> + </list-item> + <list-item> + <p> + section: § + </p> + </list-item> + <list-item> + <p> + set membership: ∈ + </p> + </list-item> + <list-item> + <p> + copyright: © + </p> + </list-item> + </list> + <p> + AT&T has an ampersand in their name. + </p> + <p> + AT&T is another way to write it. + </p> + <p> + This & that. + </p> + <p> + 4 < 5. + </p> + <p> + 6 > 5. + </p> + <p> + Backslash: \ + </p> + <p> + Backtick: ` + </p> + <p> + Asterisk: * + </p> + <p> + Underscore: _ + </p> + <p> + Left brace: { + </p> + <p> + Right brace: } + </p> + <p> + Left bracket: [ + </p> + <p> + Right bracket: ] + </p> + <p> + Left paren: ( + </p> + <p> + Right paren: ) + </p> + <p> + Greater-than: > + </p> + <p> + Hash: # + </p> + <p> + Period: . + </p> + <p> + Bang: ! + </p> + <p> + Plus: + + </p> + <p> + Minus: - + </p> + </sec> + <sec id="links"> + <title>Links</title> + <sec id="explicit"> + <title>Explicit</title> + <p> + Just a + <ext-link ext-link-type="uri" xlink:href="/url/">URL</ext-link>. + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title">URL + and title</ext-link>. + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title preceded by two spaces">URL + and title</ext-link>. + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title preceded by a tab">URL + and title</ext-link>. + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title with "quotes" in it">URL + and title</ext-link> + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="title with single quotes">URL + and title</ext-link> + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/with_underscore">with_underscore</ext-link> + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="mailto:nobody@nowhere.net">Email + link</ext-link> + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="">Empty</ext-link>. + </p> + </sec> + <sec id="reference"> + <title>Reference</title> + <p> + Foo <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>. + </p> + <p> + Foo <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>. + </p> + <p> + Foo <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>. + </p> + <p> + With <ext-link ext-link-type="uri" xlink:href="/url/">embedded + [brackets]</ext-link>. + </p> + <p> + <ext-link ext-link-type="uri" xlink:href="/url/">b</ext-link> by + itself should be a link. + </p> + <p> + Indented + <ext-link ext-link-type="uri" xlink:href="/url">once</ext-link>. + </p> + <p> + Indented + <ext-link ext-link-type="uri" xlink:href="/url">twice</ext-link>. + </p> + <p> + Indented + <ext-link ext-link-type="uri" xlink:href="/url">thrice</ext-link>. + </p> + <p> + This should [not][] be a link. + </p> + <preformat>[not]: /url</preformat> + <p> + Foo + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="Title with "quotes" inside">bar</ext-link>. + </p> + <p> + Foo + <ext-link ext-link-type="uri" xlink:href="/url/" xlink:title="Title with "quote" inside">biz</ext-link>. + </p> + </sec> + <sec id="with-ampersands"> + <title>With ampersands</title> + <p> + Here’s a + <ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&bar=2">link + with an ampersand in the URL</ext-link>. + </p> + <p> + Here’s a link with an amersand in the link text: + <ext-link ext-link-type="uri" xlink:href="http://att.com/" xlink:title="AT&T">AT&T</ext-link>. + </p> + <p> + Here’s an + <ext-link ext-link-type="uri" xlink:href="/script?foo=1&bar=2">inline + link</ext-link>. + </p> + <p> + Here’s an + <ext-link ext-link-type="uri" xlink:href="/script?foo=1&bar=2">inline + link in pointy braces</ext-link>. + </p> + </sec> + <sec id="autolinks"> + <title>Autolinks</title> + <p> + With an ampersand: + <ext-link ext-link-type="uri" xlink:href="http://example.com/?foo=1&bar=2">http://example.com/?foo=1&bar=2</ext-link> + </p> + <list list-type="bullet"> + <list-item> + <p> + In a list? + </p> + </list-item> + <list-item> + <p> + <ext-link ext-link-type="uri" xlink:href="http://example.com/">http://example.com/</ext-link> + </p> + </list-item> + <list-item> + <p> + It should. + </p> + </list-item> + </list> + <p> + An e-mail address: <email>nobody@nowhere.net</email> + </p> + <disp-quote> + <p> + Blockquoted: + <ext-link ext-link-type="uri" xlink:href="http://example.com/">http://example.com/</ext-link> + </p> + </disp-quote> + <p> + Auto-links should not occur here: + <monospace><http://example.com/></monospace> + </p> + <preformat>or here: <http://example.com/></preformat> + </sec> + </sec> + <sec id="images"> + <title>Images</title> + <p> + From “Voyage dans la Lune” by Georges Melies (1902): + </p> + <fig> + <caption>lalune</caption> + <graphic mimetype="image" mime-subtype="peg" xlink:href="lalune.jpg" xlink:title="Voyage dans la Lune" /> + </fig> + <p> + Here is a movie + <inline-graphic mimetype="image" mime-subtype="jpeg" xlink:href="movie.jpg" /> + icon. + </p> + </sec> + <sec id="footnotes"> + <title>Footnotes</title> + <p> + Here is a footnote reference,<fn> + <p> + Here is the footnote. It can go anywhere after the footnote + reference. It need not be placed at the end of the document. + </p> + </fn> and another.<fn> + <p> + Here’s the long note. This one contains multiple blocks. + </p> + <p> + Subsequent blocks are indented to show that they belong to the + footnote (as with list items). + </p> + <preformat> { <code> }</preformat> + <p> + If you want, you can indent every line, but you can also be lazy and + just indent the first line of each block. + </p> + </fn> This should <italic>not</italic> be a footnote reference, because + it contains a space.[^my note] Here is an inline note.<fn> + <p> + This is <italic>easier</italic> to type. Inline notes may contain + <ext-link ext-link-type="uri" xlink:href="http://google.com">links</ext-link> + and <monospace>]</monospace> verbatim characters, as well as + [bracketed text]. + </p> + </fn> + </p> + <disp-quote> + <p> + Notes can go in quotes.<fn> + <p> + In quote. + </p> + </fn> + </p> + </disp-quote> + <list list-type="order"> + <list-item> + <p> + And in list items.<fn> + <p> + In list. + </p> + </fn> + </p> + </list-item> + </list> + <p> + This paragraph should not be part of the note, as it is not indented. + </p> + </sec> +</body> +</article> |