From 0610f16f7f684b320325b6c0b501725138d10a52 Mon Sep 17 00:00:00 2001 From: binaarinen <53334195+binaarinen@users.noreply.github.com> Date: Sun, 19 Dec 2021 21:10:41 +0100 Subject: Add a writer for Markua 0.10 (#7729) Markua is a markdown variant used by Leanpub. More information about Markua can be found at https://leanpub.com/markua/read. Adds a new exported function `writeMarkua` from T.P.Writers.Markdown. [API change] Closes #1871. Co-authored by Tim Wisotzki and Samuel Lemmenmeier. --- MANUAL.txt | 2 + data/templates/default.markua | 21 + pandoc.cabal | 2 + src/Text/Pandoc/App/FormatHeuristics.hs | 1 + src/Text/Pandoc/Extensions.hs | 2 + src/Text/Pandoc/Shared.hs | 5 + src/Text/Pandoc/Writers.hs | 2 + src/Text/Pandoc/Writers/Markdown.hs | 102 ++++- src/Text/Pandoc/Writers/Markdown/Inline.hs | 172 +++++-- src/Text/Pandoc/Writers/Markdown/Types.hs | 3 +- test/Tests/Old.hs | 1 + test/Tests/Writers/Markua.hs | 40 ++ test/tables.markua | 58 +++ test/test-pandoc.hs | 2 + test/writer.markua | 700 +++++++++++++++++++++++++++++ 15 files changed, 1043 insertions(+), 70 deletions(-) create mode 100644 data/templates/default.markua create mode 100644 test/Tests/Writers/Markua.hs create mode 100644 test/tables.markua create mode 100644 test/writer.markua diff --git a/MANUAL.txt b/MANUAL.txt index fe551bbce..2e6d53ca6 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -316,6 +316,7 @@ header when requesting a document from a URL: - `markdown_mmd` ([MultiMarkdown]) - `markdown_phpextra` ([PHP Markdown Extra]) - `markdown_strict` (original unextended [Markdown]) + - `markua` ([Markua]) - `mediawiki` ([MediaWiki markup]) - `ms` ([roff ms]) - `muse` ([Muse]), @@ -502,6 +503,7 @@ header when requesting a document from a URL: [CSL JSON]: https://citeproc-js.readthedocs.io/en/latest/csl-json/markup.html [BibTeX]: https://ctan.org/pkg/bibtex [BibLaTeX]: https://ctan.org/pkg/biblatex +[Markua]: https://leanpub.com/markua/read ## Reader options {.options} diff --git a/data/templates/default.markua b/data/templates/default.markua new file mode 100644 index 000000000..9f6ca96de --- /dev/null +++ b/data/templates/default.markua @@ -0,0 +1,21 @@ +$if(titleblock)$ +$titleblock$ + +$endif$ +$for(header-includes)$ +$header-includes$ + +$endfor$ +$for(include-before)$ +$include-before$ + +$endfor$ +$if(toc)$ +$table-of-contents$ + +$endif$ +$body$ +$for(include-after)$ + +$include-after$ +$endfor$ diff --git a/pandoc.cabal b/pandoc.cabal index b09b19144..3cad5bce7 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -90,6 +90,7 @@ data-files: data/templates/default.epub3 data/templates/article.jats_publishing data/templates/affiliations.jats + data/templates/default.markua -- translations data/translations/*.yaml -- source files for reference.docx @@ -825,6 +826,7 @@ test-suite test-pandoc Tests.Writers.Docx Tests.Writers.RST Tests.Writers.TEI + Tests.Writers.Markua Tests.Writers.Muse Tests.Writers.FB2 Tests.Writers.Powerpoint diff --git a/src/Text/Pandoc/App/FormatHeuristics.hs b/src/Text/Pandoc/App/FormatHeuristics.hs index a2acfc6d6..e5fe7ad81 100644 --- a/src/Text/Pandoc/App/FormatHeuristics.hs +++ b/src/Text/Pandoc/App/FormatHeuristics.hs @@ -54,6 +54,7 @@ formatFromFilePath x = ".lhs" -> Just "markdown+lhs" ".ltx" -> Just "latex" ".markdown" -> Just "markdown" + ".markua" -> Just "markua" ".mkdn" -> Just "markdown" ".mkd" -> Just "markdown" ".mdwn" -> Just "markdown" diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index ce6a95458..33f615740 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -432,6 +432,8 @@ getDefaultExtensions "jats_archiving" = getDefaultExtensions "jats" getDefaultExtensions "jats_publishing" = getDefaultExtensions "jats" getDefaultExtensions "jats_articleauthoring" = getDefaultExtensions "jats" getDefaultExtensions "opml" = pandocExtensions -- affects notes +getDefaultExtensions "markua" = extensionsFromList + [] getDefaultExtensions _ = extensionsFromList [Ext_auto_identifiers] diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index eb0b4acbf..50abe6937 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -25,6 +25,7 @@ module Text.Pandoc.Shared ( ordNub, findM, -- * Text processing + inquotes, tshow, elemText, notElemText, @@ -186,6 +187,10 @@ findM p = foldr go (pure Nothing) -- Text processing -- +-- | Wrap double quotes around a Text +inquotes :: T.Text -> T.Text +inquotes txt = T.cons '\"' (T.snoc txt '\"') + tshow :: Show a => a -> T.Text tshow = T.pack . show diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index c348477c2..960b9074c 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -51,6 +51,7 @@ module Text.Pandoc.Writers , writeLaTeX , writeMan , writeMarkdown + , writeMarkua , writeMediaWiki , writeMs , writeMuse @@ -190,6 +191,7 @@ writers = [ ,("csljson" , TextWriter writeCslJson) ,("bibtex" , TextWriter writeBibTeX) ,("biblatex" , TextWriter writeBibLaTeX) + ,("markua" , TextWriter writeMarkua) ] -- | Retrieve writer, extensions based on formatSpec (format+extensions). diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 022dbc24f..bb68d9fee 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -18,6 +18,7 @@ Markdown: module Text.Pandoc.Writers.Markdown ( writeMarkdown, writeCommonMark, + writeMarkua, writePlain) where import Control.Monad.Reader import Control.Monad.State.Strict @@ -42,7 +43,10 @@ import Text.Pandoc.Templates (renderTemplate) import Text.DocTemplates (Val(..), Context(..), FromContext(..)) import Text.Pandoc.Walk import Text.Pandoc.Writers.HTML (writeHtml5String) -import Text.Pandoc.Writers.Markdown.Inline (inlineListToMarkdown, linkAttributes, attrsToMarkdown) +import Text.Pandoc.Writers.Markdown.Inline (inlineListToMarkdown, + linkAttributes, + attrsToMarkdown, + attrsToMarkua) import Text.Pandoc.Writers.Markdown.Types (MarkdownVariant(..), WriterState(..), WriterEnv(..), @@ -77,6 +81,26 @@ writeCommonMark opts document = enableExtension Ext_intraword_underscores $ writerExtensions opts } +-- | Convert Pandoc to Markua. +writeMarkua :: PandocMonad m => WriterOptions -> Pandoc -> m Text +writeMarkua opts document = + evalMD (pandocToMarkdown opts' document) def{ envVariant = Markua } def + where + opts' = opts{ writerExtensions = + enableExtension Ext_hard_line_breaks $ + enableExtension Ext_pipe_tables $ + -- required for fancy list enumerators + enableExtension Ext_fancy_lists $ + enableExtension Ext_startnum $ + enableExtension Ext_strikeout $ + enableExtension Ext_subscript $ + enableExtension Ext_superscript $ + enableExtension Ext_definition_lists $ + enableExtension Ext_smart $ + enableExtension Ext_footnotes + mempty } + + pandocTitleBlock :: Doc Text -> [Doc Text] -> Doc Text -> Doc Text pandocTitleBlock tit auths dat = hang 2 (text "% ") tit <> cr <> @@ -327,8 +351,15 @@ blockToMarkdown' opts (Div attrs ils) = do contents <- blockListToMarkdown opts ils variant <- asks envVariant return $ - case () of - _ | isEnabled Ext_fenced_divs opts && + case () of + _ | variant == Markua -> + case () of + () | "blurb" `elem` classes' -> prefixed "B> " contents <> blankline + | "aside" `elem` classes' -> prefixed "A> " contents <> blankline + -- | necessary to enable option to create a bibliography + | (take 3 (T.unpack id')) == "ref" -> contents <> blankline + | otherwise -> contents <> blankline + | isEnabled Ext_fenced_divs opts && attrs /= nullAttr -> let attrsToMd = if variant == Commonmark then attrsToMarkdown @@ -408,6 +439,7 @@ blockToMarkdown' opts b@(RawBlock f str) = do | f `elem` ["markdown", "markdown_github", "markdown_phpextra", "markdown_mmd", "markdown_strict"] -> return $ literal str <> literal "\n" + Markua -> renderEmpty _ | isEnabled Ext_raw_attribute opts -> rawAttribBlock | f `elem` ["html", "html5", "html4"] , isEnabled Ext_markdown_attribute opts @@ -419,17 +451,19 @@ blockToMarkdown' opts b@(RawBlock f str) = do , isEnabled Ext_raw_tex opts -> return $ literal str <> literal "\n" _ -> renderEmpty -blockToMarkdown' opts HorizontalRule = - return $ blankline <> literal (T.replicate (writerColumns opts) "-") <> blankline +blockToMarkdown' opts HorizontalRule = do + variant <- asks envVariant + let indicator = case variant of + Markua -> "* * *" + _ -> T.replicate (writerColumns opts) "-" + return $ blankline <> literal indicator <> blankline blockToMarkdown' opts (Header level attr inlines) = do - -- first, if we're putting references at the end of a section, we -- put them here. blkLevel <- asks envBlockLevel refs <- if writerReferenceLocation opts == EndOfSection && blkLevel == 1 then notesAndRefs opts else return empty - variant <- asks envVariant -- we calculate the id that would be used by auto_identifiers -- so we know whether to print an explicit identifier @@ -442,7 +476,8 @@ blockToMarkdown' opts (Header level attr inlines) = do && id' == autoId -> empty (id',_,_) | isEnabled Ext_mmd_header_identifiers opts -> space <> brackets (literal id') - _ | isEnabled Ext_header_attributes opts || + _ | variant == Markua -> attrsToMarkua attr + | isEnabled Ext_header_attributes opts || isEnabled Ext_attributes opts -> space <> attrsToMarkdown attr | otherwise -> empty @@ -476,6 +511,8 @@ blockToMarkdown' opts (Header level attr inlines) = do -- ghc interprets '#' characters in column 1 as linenum specifiers. _ | variant == PlainText || isEnabled Ext_literate_haskell opts -> contents <> blankline + _ | variant == Markua -> attr' <> cr <> literal (T.replicate level "#") + <> space <> contents <> blankline _ -> literal (T.replicate level "#") <> space <> contents <> attr' <> blankline return $ refs <> hdr @@ -492,9 +529,11 @@ blockToMarkdown' opts (CodeBlock attribs str) = do backticks <> attrs <> cr <> literal str <> cr <> backticks <> blankline | isEnabled Ext_fenced_code_blocks opts -> tildes <> attrs <> cr <> literal str <> cr <> tildes <> blankline - _ -> nest (writerTabStop opts) (literal str) <> blankline + _ | variant == Markua -> blankline <> attrsToMarkua attribs <> cr <> backticks <> cr <> + literal str <> cr <> backticks <> cr <> blankline + | otherwise -> nest (writerTabStop opts) (literal str) <> blankline where - endlineLen c = maybe 3 ((+1) . maximum) $ nonEmpty $ + endlineLen c = maybe 3 ((+1) . maximum) $ nonEmpty [T.length ln | ln <- map trim (T.lines str) , T.pack [c,c,c] `T.isPrefixOf` ln @@ -581,24 +620,29 @@ blockToMarkdown' opts t@(Table _ blkCapt specs thead tbody tfoot) = do return $ nst (tbl $$ caption'') $$ blankline blockToMarkdown' opts (BulletList items) = do contents <- inList $ mapM (bulletListItemToMarkdown opts) items - return $ (if isTightList items then vcat else vsep) contents <> blankline + return $ (if isTightList items then vcat else vsep) + contents <> blankline blockToMarkdown' opts (OrderedList (start,sty,delim) items) = do variant <- asks envVariant let start' = if variant == Commonmark || isEnabled Ext_startnum opts then start else 1 let sty' = if isEnabled Ext_fancy_lists opts then sty else DefaultStyle - let delim' = if isEnabled Ext_fancy_lists opts - then delim - else if variant == Commonmark && - (delim == OneParen || delim == TwoParens) - then OneParen -- commonmark only supports one paren - else DefaultDelim + let delim' | isEnabled Ext_fancy_lists opts = + case variant of + -- Markua supports 'fancy' enumerators, but no TwoParens + Markua -> if delim == TwoParens then OneParen else delim + _ -> delim + | variant == Commonmark && --commonmark only supports one paren + (delim == OneParen || delim == TwoParens) = OneParen + | otherwise = DefaultDelim let attribs = (start', sty', delim') let markers = orderedListMarkers attribs - let markers' = map (\m -> if T.length m < 3 - then m <> T.replicate (3 - T.length m) " " - else m) markers + let markers' = case variant of + Markua -> markers + _ -> map (\m -> if T.length m < 3 + then m <> T.replicate (3 - T.length m) " " + else m) markers contents <- inList $ zipWithM (orderedListItemToMarkdown opts) markers' items return $ (if isTightList items then vcat else vsep) contents <> blankline @@ -712,10 +756,13 @@ itemEndsWithTightList bs = -- | Convert bullet list item (list of blocks) to markdown. bulletListItemToMarkdown :: PandocMonad m => WriterOptions -> [Block] -> MD m (Doc Text) bulletListItemToMarkdown opts bs = do + variant <- asks envVariant let exts = writerExtensions opts contents <- blockListToMarkdown opts $ taskListItemToAscii exts bs let sps = T.replicate (writerTabStop opts - 2) " " - let start = literal $ "- " <> sps + let start = case variant of + Markua -> literal "* " + _ -> literal $ "- " <> sps -- remove trailing blank line if item ends with a tight list let contents' = if itemEndsWithTightList bs then chomp contents <> cr @@ -725,19 +772,22 @@ bulletListItemToMarkdown opts bs = do -- | Convert ordered list item (a list of blocks) to markdown. orderedListItemToMarkdown :: PandocMonad m => WriterOptions -- ^ options - -> Text -- ^ list item marker + -> Text -- ^ list item marker -> [Block] -- ^ list item (list of blocks) -> MD m (Doc Text) orderedListItemToMarkdown opts marker bs = do let exts = writerExtensions opts contents <- blockListToMarkdown opts $ taskListItemToAscii exts bs + variant <- asks envVariant let sps = case writerTabStop opts - T.length marker of n | n > 0 -> literal $ T.replicate n " " _ -> literal " " let ind = if isEnabled Ext_four_space_rule opts then writerTabStop opts else max (writerTabStop opts) (T.length marker + 1) - let start = literal marker <> sps + let start = case variant of + Markua -> literal marker <> " " + _ -> literal marker <> sps -- remove trailing blank line if item ends with a tight list let contents' = if itemEndsWithTightList bs then chomp contents <> cr @@ -756,7 +806,10 @@ definitionListItemToMarkdown opts (label, defs) = do then do let tabStop = writerTabStop opts variant <- asks envVariant - let leader = if variant == PlainText then " " else ": " + let leader = case variant of + PlainText -> " " + Markua -> ":" + _ -> ": " let sps = case writerTabStop opts - 3 of n | n > 0 -> literal $ T.replicate n " " _ -> literal " " @@ -827,6 +880,7 @@ blockListToMarkdown opts blocks = do isListBlock _ = False commentSep | variant == PlainText = Null + | variant == Markua = Null | isEnabled Ext_raw_html opts = RawBlock "html" "\n" | otherwise = RawBlock "markdown" " \n" mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks) diff --git a/src/Text/Pandoc/Writers/Markdown/Inline.hs b/src/Text/Pandoc/Writers/Markdown/Inline.hs index d299d31b2..0bf70e80e 100644 --- a/src/Text/Pandoc/Writers/Markdown/Inline.hs +++ b/src/Text/Pandoc/Writers/Markdown/Inline.hs @@ -13,7 +13,8 @@ module Text.Pandoc.Writers.Markdown.Inline ( inlineListToMarkdown, linkAttributes, - attrsToMarkdown + attrsToMarkdown, + attrsToMarkua ) where import Control.Monad.Reader import Control.Monad.State.Strict @@ -95,6 +96,11 @@ escapeText opts = T.pack . go' . T.unpack , isAlphaNum x -> c : '_' : x : go xs _ -> c : go cs +-- Escape the escape character, as well as formatting pairs +escapeMarkuaString :: Text -> Text +escapeMarkuaString s = foldr (uncurry T.replace) s [("--","~-~-"), + ("**","~*~*"),("//","~/~/"),("^^","~^~^"),(",,","~,~,")] + attrsToMarkdown :: Attr -> Doc Text attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys] where attribId = case attribs of @@ -116,9 +122,56 @@ attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys] escAttrChar '\\' = literal "\\\\" escAttrChar c = literal $ T.singleton c +attrsToMarkua:: Attr -> Doc Text +attrsToMarkua attributes + | null list = empty + | otherwise = braces $ intercalateDocText list + where attrId = case attributes of + ("",_,_) -> [] + (i,_,_) -> [literal $ "id: " <> i] + -- all non explicit (key,value) attributes besides id are getting + -- a default class key to be Markua conform + attrClasses = case attributes of + (_,[],_) -> [] + (_,classes,_) -> map (escAttr . ("class: " <>)) + classes + attrKeyValues = case attributes of + (_,_,[]) -> [] + (_,_,keyvalues) -> map ((\(k,v) -> escAttr k + <> ": " <> escAttr v) . + preprocessKeyValues) keyvalues + escAttr = mconcat . map escAttrChar . T.unpack + escAttrChar '"' = literal "\"" + escAttrChar c = literal $ T.singleton c + + list = concat [attrId, attrClasses, attrKeyValues] + + -- if attribute key is alt, caption, title then content + -- gets wrapped inside quotes + -- attribute gets removed + preprocessKeyValues :: (Text, Text) -> (Text, Text) + preprocessKeyValues (key,value) + | key == "alt" || + key == "caption" || + key == "title" = (key, inquotes value) + | otherwise = (key,value) + intercalateDocText :: [Doc Text] -> Doc Text + intercalateDocText [] = empty + intercalateDocText [x] = x + intercalateDocText (x:xs) = x <> ", " <> (intercalateDocText xs) + +-- | Add a (key, value) pair to Pandoc attr type +addKeyValueToAttr :: Attr -> (Text,Text) -> Attr +addKeyValueToAttr (ident,classes,kvs) (key,value) + | not (T.null key) && not (T.null value) = (ident, + classes, + (key,value): kvs) + | otherwise = (ident,classes,kvs) + linkAttributes :: WriterOptions -> Attr -> Doc Text linkAttributes opts attr = - if (isEnabled Ext_link_attributes opts || isEnabled Ext_attributes opts) && attr /= nullAttr + if (isEnabled Ext_link_attributes opts || + isEnabled Ext_attributes opts) && attr /= nullAttr then attrsToMarkdown attr else empty @@ -283,6 +336,7 @@ inlineToMarkdown opts (Span attrs ils) = do _ -> id $ case variant of PlainText -> contents + Markua -> "`" <> contents <> "`" <> attrsToMarkua attrs _ | attrs == nullAttr -> contents | isEnabled Ext_bracketed_spans opts -> let attrs' = if attrs /= nullAttr @@ -396,60 +450,75 @@ inlineToMarkdown opts (Quoted DoubleQuote lst) = do then "“" <> contents <> "”" else "“" <> contents <> "”" inlineToMarkdown opts (Code attr str) = do + variant <- asks envVariant let tickGroups = filter (T.any (== '`')) $ T.group str let longest = maybe 0 maximum $ nonEmpty $ map T.length tickGroups let marker = T.replicate (longest + 1) "`" let spacer = if longest == 0 then "" else " " let attrsEnabled = isEnabled Ext_inline_code_attributes opts || isEnabled Ext_attributes opts - let attrs = if attrsEnabled && attr /= nullAttr - then attrsToMarkdown attr - else empty - variant <- asks envVariant + let attrs = case variant of + Markua -> attrsToMarkua attr + _ -> if attrsEnabled && attr /= nullAttr + then attrsToMarkdown attr + else empty case variant of PlainText -> return $ literal str _ -> return $ literal (marker <> spacer <> str <> spacer <> marker) <> attrs inlineToMarkdown opts (Str str) = do variant <- asks envVariant - let str' = (if writerPreferAscii opts - then toHtml5Entities - else id) . - (if isEnabled Ext_smart opts - then unsmartify opts - else id) . - (if variant == PlainText - then id - else escapeText opts) $ str + let str' = case variant of + Markua -> escapeMarkuaString str + _ -> (if writerPreferAscii opts + then toHtml5Entities + else id) . + (if isEnabled Ext_smart opts + then unsmartify opts + else id) . + (if variant == PlainText + then id + else escapeText opts) $ str return $ literal str' -inlineToMarkdown opts (Math InlineMath str) = - case writerHTMLMathMethod opts of - WebTeX url -> inlineToMarkdown opts - (Image nullAttr [Str str] (url <> urlEncode str, str)) - _ | isEnabled Ext_tex_math_dollars opts -> - return $ "$" <> literal str <> "$" - | isEnabled Ext_tex_math_single_backslash opts -> - return $ "\\(" <> literal str <> "\\)" - | isEnabled Ext_tex_math_double_backslash opts -> - return $ "\\\\(" <> literal str <> "\\\\)" - | otherwise -> do - variant <- asks envVariant - texMathToInlines InlineMath str >>= - inlineListToMarkdown opts . - (if variant == PlainText then makeMathPlainer else id) -inlineToMarkdown opts (Math DisplayMath str) = - case writerHTMLMathMethod opts of - WebTeX url -> (\x -> blankline <> x <> blankline) `fmap` - inlineToMarkdown opts (Image nullAttr [Str str] - (url <> urlEncode str, str)) - _ | isEnabled Ext_tex_math_dollars opts -> - return $ "$$" <> literal str <> "$$" - | isEnabled Ext_tex_math_single_backslash opts -> - return $ "\\[" <> literal str <> "\\]" - | isEnabled Ext_tex_math_double_backslash opts -> - return $ "\\\\[" <> literal str <> "\\\\]" - | otherwise -> (\x -> cr <> x <> cr) `fmap` - (texMathToInlines DisplayMath str >>= inlineListToMarkdown opts) +inlineToMarkdown opts (Math InlineMath str) = do + variant <- asks envVariant + case () of + _ | variant == Markua -> return $ "`" <> literal str <> "`" <> "$" + | otherwise -> case writerHTMLMathMethod opts of + WebTeX url -> inlineToMarkdown opts + (Image nullAttr [Str str] (url <> urlEncode str, str)) + _ | isEnabled Ext_tex_math_dollars opts -> + return $ "$" <> literal str <> "$" + | isEnabled Ext_tex_math_single_backslash opts -> + return $ "\\(" <> literal str <> "\\)" + | isEnabled Ext_tex_math_double_backslash opts -> + return $ "\\\\(" <> literal str <> "\\\\)" + | otherwise -> + texMathToInlines InlineMath str >>= + inlineListToMarkdown opts . + (if variant == PlainText then makeMathPlainer else id) + +inlineToMarkdown opts (Math DisplayMath str) = do + variant <- asks envVariant + case () of + _ | variant == Markua -> do + let attributes = attrsToMarkua (addKeyValueToAttr ("",[],[]) + ("format", "latex")) + return $ blankline <> attributes <> cr <> literal "```" <> cr + <> literal str <> cr <> literal "```" <> blankline + | otherwise -> case writerHTMLMathMethod opts of + WebTeX url -> (\x -> blankline <> x <> blankline) `fmap` + inlineToMarkdown opts (Image nullAttr [Str str] + (url <> urlEncode str, str)) + _ | isEnabled Ext_tex_math_dollars opts -> + return $ "$$" <> literal str <> "$$" + | isEnabled Ext_tex_math_single_backslash opts -> + return $ "\\[" <> literal str <> "\\]" + | isEnabled Ext_tex_math_double_backslash opts -> + return $ "\\\\[" <> literal str <> "\\\\]" + | otherwise -> (\x -> cr <> x <> cr) `fmap` + (texMathToInlines DisplayMath str >>= inlineListToMarkdown opts) + inlineToMarkdown opts il@(RawInline f str) = do let tickGroups = filter (T.any (== '`')) $ T.group str let numticks = 1 + maybe 0 maximum (nonEmpty (map T.length tickGroups)) @@ -469,6 +538,7 @@ inlineToMarkdown opts il@(RawInline f str) = do | f `elem` ["markdown", "markdown_github", "markdown_phpextra", "markdown_mmd", "markdown_strict"] -> return $ literal str + Markua -> renderEmpty _ | isEnabled Ext_raw_attribute opts -> rawAttribInline | f `elem` ["html", "html5", "html4"] , isEnabled Ext_raw_html opts @@ -563,6 +633,11 @@ inlineToMarkdown opts lnk@(Link attr@(ident,classes,kvs) txt (src, tit)) = do PlainText | useAuto -> return $ literal srcSuffix | otherwise -> return linktext + Markua + | T.null tit -> return $ result <> attrsToMarkua attr + | otherwise -> return $ result <> attrsToMarkua attributes + where result = "[" <> linktext <> "](" <> (literal src) <> ")" + attributes = addKeyValueToAttr attr ("title", tit) _ | useAuto -> return $ "<" <> literal srcSuffix <> ">" | useRefLinks -> let first = "[" <> linktext <> "]" @@ -594,9 +669,16 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit)) then [Str ""] else alternate linkPart <- inlineToMarkdown opts (Link attr txt (source, tit)) + alt <- inlineListToMarkdown opts alternate + let attributes | variant == Markua = attrsToMarkua $ + addKeyValueToAttr (addKeyValueToAttr attr ("title", tit)) + ("alt", render (Just (writerColumns opts)) alt) + | otherwise = empty return $ case variant of - PlainText -> "[" <> linkPart <> "]" - _ -> "!" <> linkPart + PlainText -> "[" <> linkPart <> "]" + Markua -> cr <> attributes <> cr <> literal "![](" <> + literal source <> ")" <> cr + _ -> "!" <> linkPart inlineToMarkdown opts (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get diff --git a/src/Text/Pandoc/Writers/Markdown/Types.hs b/src/Text/Pandoc/Writers/Markdown/Types.hs index a1d0d14e4..060446811 100644 --- a/src/Text/Pandoc/Writers/Markdown/Types.hs +++ b/src/Text/Pandoc/Writers/Markdown/Types.hs @@ -45,7 +45,8 @@ data WriterEnv = WriterEnv { envInList :: Bool } data MarkdownVariant = - PlainText + Markua + | PlainText | Commonmark | Markdown deriving (Show, Eq) diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index e03d94e85..450449946 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -228,6 +228,7 @@ tests pandocPath = , test' "reader" ["-f", "ipynb", "-t", "html"] "ipynb/rank.ipynb" "ipynb/rank.out.html" ] + , testGroup "markua" [ testGroup "writer" $ writerTests' "markua"] ] where test' = test pandocPath diff --git a/test/Tests/Writers/Markua.hs b/test/Tests/Writers/Markua.hs new file mode 100644 index 000000000..62239f3da --- /dev/null +++ b/test/Tests/Writers/Markua.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Markua (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +{- + "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) -> TestTree +(=:) = test (purely (writeMarkua def) . toPandoc) + +tests :: [TestTree] +tests = [ testGroup "simple blurb/aside" + ["blurb" =: divWith ("",["blurb"],[]) (bulletList [para "blurb content"]) + =?> "B> * blurb content" + ,"aside" =: divWith ("",["aside"],[]) (bulletList [para "aside list"]) + =?> "A> * aside list" + ] + ,testGroup "multiclass blurb/aside" + ["blurb" =: divWith ("",["blurb", "otherclass"],[]) (bulletList [para "blurb content"]) + =?> "B> * blurb content" + ,"aside" =: divWith ("",["otherclass", "aside"],[]) (bulletList [para "aside list"]) + =?> "A> * aside list" + ] + ] diff --git a/test/tables.markua b/test/tables.markua new file mode 100644 index 000000000..b82264fd7 --- /dev/null +++ b/test/tables.markua @@ -0,0 +1,58 @@ +Simple table with caption: + +| Right | Left | Center | Default | +|------:|:-----|:------:|---------| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Demonstration of simple table syntax. + +Simple table without caption: + +| Right | Left | Center | Default | +|------:|:-----|:------:|---------| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Simple table indented two spaces: + +| Right | Left | Center | Default | +|------:|:-----|:------:|---------| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Demonstration of simple table syntax. + +Multiline table with caption: + +| Centered Header | Left Aligned | Right Aligned | Default aligned | +|:---------------:|:-------------|--------------:|:------------------------------------------------------| +| First | row | 12.0 | Example of a row that spans multiple lines. | +| Second | row | 5.0 | Here’s another one. Note the blank line between rows. | + +Here’s the caption. It may span multiple lines. + +Multiline table without caption: + +| Centered Header | Left Aligned | Right Aligned | Default aligned | +|:---------------:|:-------------|--------------:|:------------------------------------------------------| +| First | row | 12.0 | Example of a row that spans multiple lines. | +| Second | row | 5.0 | Here’s another one. Note the blank line between rows. | + +Table without column headers: + +| | | | | +|----:|:----|:---:|----:| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Multiline table without column headers: + +| | | | | +|:------:|:----|-----:|-------------------------------------------------------| +| First | row | 12.0 | Example of a row that spans multiple lines. | +| Second | row | 5.0 | Here’s another one. Note the blank line between rows. | diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 476762aac..fcb157fb7 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -50,6 +50,7 @@ import qualified Tests.Writers.Powerpoint import qualified Tests.Writers.RST import qualified Tests.Writers.AnnotatedTable import qualified Tests.Writers.TEI +import qualified Tests.Writers.Markua import Text.Pandoc.Shared (inDirectory) tests :: FilePath -> TestTree @@ -72,6 +73,7 @@ tests pandocPath = testGroup "pandoc tests" , testGroup "Docx" Tests.Writers.Docx.tests , testGroup "RST" Tests.Writers.RST.tests , testGroup "TEI" Tests.Writers.TEI.tests + , testGroup "markua" Tests.Writers.Markua.tests , testGroup "Muse" Tests.Writers.Muse.tests , testGroup "FB2" Tests.Writers.FB2.tests , testGroup "PowerPoint" Tests.Writers.Powerpoint.tests diff --git a/test/writer.markua b/test/writer.markua new file mode 100644 index 000000000..1c5b44cc2 --- /dev/null +++ b/test/writer.markua @@ -0,0 +1,700 @@ +This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +markdown test suite. + +* * * + +{id: headers} +# Headers + +{id: level-2-with-an-embedded-link} +## Level 2 with an [embedded link](/url) + +{id: level-3-with-emphasis} +### Level 3 with *emphasis* + +{id: level-4} +#### Level 4 + +{id: level-5} +##### Level 5 + +{id: level-1} +# Level 1 + +{id: level-2-with-emphasis} +## Level 2 with *emphasis* + +{id: level-3} +### Level 3 + +with no blank line + +{id: level-2} +## Level 2 + +with no blank line + +* * * + +{id: paragraphs} +# Paragraphs + +Here’s a regular paragraph. + +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. + +Here’s one with a bullet. * criminey. + +There should be a hard line break +here. + +* * * + +{id: block-quotes} +# Block Quotes + +E-mail style: + +> This is a block quote. It is pretty short. + +> Code in a block quote: +> +> ``` +> sub status { +> print "working"; +> } +> ``` +> +> A list: +> +> 1. item one +> 2. item two +> +> Nested block quotes: +> +> > nested +> +> > nested + +This should not be a block quote: 2 > 1. + +And a following paragraph. + +* * * + +{id: code-blocks} +# Code Blocks + +Code: + +``` +---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab +``` + +And: + +``` + this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ +``` + +* * * + +{id: lists} +# Lists + +{id: unordered} +## Unordered + +Asterisks tight: + +* asterisk 1 +* asterisk 2 +* asterisk 3 + +Asterisks loose: + +* asterisk 1 + +* asterisk 2 + +* asterisk 3 + +Pluses tight: + +* Plus 1 +* Plus 2 +* Plus 3 + +Pluses loose: + +* Plus 1 + +* Plus 2 + +* Plus 3 + +Minuses tight: + +* Minus 1 +* Minus 2 +* Minus 3 + +Minuses loose: + +* Minus 1 + +* Minus 2 + +* Minus 3 + +{id: ordered} +## Ordered + +Tight: + +1. First +2. Second +3. Third + +and: + +1. One +2. Two +3. Three + +Loose using tabs: + +1. First + +2. Second + +3. Third + +and using spaces: + +1. One + +2. Two + +3. Three + +Multiple paragraphs: + +1. Item 1, graf one. + + Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. + +2. Item 2. + +3. Item 3. + +{id: nested} +## Nested + +* Tab + * Tab + * Tab + +Here’s another: + +1. First +2. Second: + * Fee + * Fie + * Foe +3. Third + +Same thing but with paragraphs: + +1. First + +2. Second: + + * Fee + * Fie + * Foe + +3. Third + +{id: tabs-and-spaces} +## Tabs and spaces + +* this is a list item indented with tabs + +* this is a list item indented with spaces + + * this is an example list item indented with tabs + + * this is an example list item indented with spaces + +{id: fancy-list-markers} +## Fancy list markers + +2) begins with 2 + +3) and now 3 + + with a continuation + + iv. sublist with roman numerals, starting with 4 + v. more items + A) a subsublist + B) a subsublist + +Nesting: + +A. Upper Alpha + I. Upper Roman. + 6) Decimal start with 6 + c) Lower alpha with paren + +Autonumbering: + +1. Autonumber. +2. More. + 1. Nested. + +Should not be a list item: + +M.A. 2007 + +B. Williams + +* * * + +{id: definition-lists} +# Definition Lists + +Tight using spaces: + +apple +: red fruit + +orange +: orange fruit + +banana +: yellow fruit + +Tight using tabs: + +apple +: red fruit + +orange +: orange fruit + +banana +: yellow fruit + +Loose: + +apple + +: red fruit + +orange + +: orange fruit + +banana + +: yellow fruit + +Multiple blocks with italics: + +*apple* + +: red fruit + + contains seeds, crisp, pleasant to taste + +*orange* + +: orange fruit + + ``` + { orange code block } + ``` + + > orange block quote + +Multiple definitions, tight: + +apple +: red fruit +: computer + +orange +: orange fruit +: bank + +Multiple definitions, loose: + +apple + +: red fruit + +: computer + +orange + +: orange fruit + +: bank + +Blank line after term, indented marker, alternate markers: + +apple + +: red fruit + +: computer + +orange + +: orange fruit + + 1. sublist + 2. sublist + +{id: html-blocks} +# HTML Blocks + +Simple block on one line: + +foo + +And nested without indentation: + +foo + +bar + +Interpreted markdown in a table: + +This is *emphasized* +And this is **strong** +Here’s a simple block: + +foo + +This should be a code block, though: + +``` +
+ foo +
+``` + +As should this: + +``` +
foo
+``` + +Now, nested: + +foo + +This should just be an HTML comment: + +Multiline: + +Code block: + +``` + +``` + +Just plain comment, with trailing spaces on the line: + +Code: + +``` +
+``` + +Hr’s: + +* * * + +{id: inline-markup} +# Inline Markup + +This is *emphasized*, and so *is this*. + +This is **strong**, and so **is this**. + +An *[emphasized link](/url)*. + +***This is strong and em.*** + +So is ***this*** word. + +***This is strong and em.*** + +So is ***this*** word. + +This is code: `>`, `$`, `\`, `\$`, ``. + +~~This is *strikeout*.~~ + +Superscripts: a^bc^d a^*hello*^ a^hello there^. + +Subscripts: H~2~O, H~23~O, H~many of them~O. + +These should not be superscripts or subscripts, because of the unescaped spaces: +a^b c^d, a~b c~d. + +* * * + +{id: smart-quotes-ellipses-dashes} +# Smart quotes, ellipses, dashes + +"Hello," said the spider. "'Shelob' is my name." + +'A', 'B', and 'C' are letters. + +'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.' + +'He said, "I want to go."' Were you alive in the 70’s? + +Here is some quoted '`code`' and a "[quoted +link](http://example.com/?foo=1&bar=2)". + +Some dashes: one—two — three—four — five. + +Dashes between numbers: 5–7, 255–66, 1987–1999. + +Ellipses…and…and…. + +* * * + +{id: latex} +# LaTeX + +* +* `2+2=4`$ +* `x \in y`$ +* `\alpha \wedge \omega`$ +* `223`$ +* `p`$-Tree +* Here’s some display math: + + {format: latex} + ``` + \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h} + ``` +* Here’s one that has a line break in it: `\alpha + \omega \times x^2`$. + +These shouldn’t be math: + +* To get the famous equation, write `$e = mc^2$`. +* $22,000 is a *lot* of money. So is $34,000. (It worked if "lot" is + emphasized.) +* Shoes ($20) and socks ($5). +* Escaped `$`: $73 *this should be emphasized* 23$. + +Here’s a LaTeX table: + +* * * + +{id: special-characters} +# Special Characters + +Here is some unicode: + +* I hat: Î +* o umlaut: ö +* section: § +* set membership: ∈ +* copyright: © + +AT&T has an ampersand in their name. + +AT&T is another way to write it. + +This & that. + +4 < 5. + +6 > 5. + +Backslash: \ + +Backtick: ` + +Asterisk: * + +Underscore: _ + +Left brace: { + +Right brace: } + +Left bracket: [ + +Right bracket: ] + +Left paren: ( + +Right paren: ) + +Greater-than: > + +Hash: # + +Period: . + +Bang: ! + +Plus: + + +Minus: - + +* * * + +{id: links} +# Links + +{id: explicit} +## Explicit + +Just a [URL](/url/). + +[URL and title](/url/){title: "title"}. + +[URL and title](/url/){title: "title preceded by two spaces"}. + +[URL and title](/url/){title: "title preceded by a tab"}. + +[URL and title](/url/){title: "title with "quotes" in it"} + +[URL and title](/url/){title: "title with single quotes"} + +[with_underscore](/url/with_underscore) + +[Email link](mailto:nobody@nowhere.net) + +[Empty](). + +{id: reference} +## Reference + +Foo [bar](/url/). + +With [embedded [brackets]](/url/). + +[b](/url/) by itself should be a link. + +Indented [once](/url). + +Indented [twice](/url). + +Indented [thrice](/url). + +This should [not][] be a link. + +``` +[not]: /url +``` + +Foo [bar](/url/){title: "Title with "quotes" inside"}. + +Foo [biz](/url/){title: "Title with "quote" inside"}. + +{id: with-ampersands} +## With ampersands + +Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). + +Here’s a link with an amersand in the link text: +[AT&T](http://att.com/){title: "AT&T"}. + +Here’s an [inline link](/script?foo=1&bar=2). + +Here’s an [inline link in pointy braces](/script?foo=1&bar=2). + +{id: autolinks} +## Autolinks + +With an ampersand: +[http:~/~/example.com/?foo=1&bar=2](http://example.com/?foo=1&bar=2){class: uri} + +* In a list? +* [http:~/~/example.com/](http://example.com/){class: uri} +* It should. + +An e-mail address: [nobody@nowhere.net](mailto:nobody@nowhere.net){class: email} + +> Blockquoted: [http:~/~/example.com/](http://example.com/){class: uri} + +Auto-links should not occur here: `` + +``` +or here: +``` + +* * * + +{id: images} +# Images + +From "Voyage dans la Lune" by Georges Melies (1902): + +{alt: "lalune", title: "Voyage dans la Lune"} +![](lalune.jpg) + +Here is a movie +{alt: "movie"} +![](movie.jpg) +icon. + +* * * + +{id: footnotes} +# Footnotes + +Here is a footnote reference,[^1] and another.[^2] This should *not* be a +footnote reference, because it contains a space.[^my note] Here is an inline +note.[^3] + +> Notes can go in quotes.[^4] + +1. And in list items.[^5] + +This paragraph should not be part of the note, as it is not indented. + +[^1]: Here is the footnote. It can go anywhere after the footnote reference. It + need not be placed at the end of the document. + +[^2]: Here’s the long note. This one contains multiple blocks. + + Subsequent blocks are indented to show that they belong to the footnote (as + with list items). + + ``` + { } + ``` + + If you want, you can indent every line, but you can also be lazy and just + indent the first line of each block. + +[^3]: This is *easier* to type. Inline notes may contain + [links](http://google.com) and `]` verbatim characters, as well as + [bracketed text]. + +[^4]: In quote. + +[^5]: In list. -- cgit v1.2.3