diff options
author | Alexander Krotov <ilabdsf@gmail.com> | 2017-03-10 13:16:27 +0400 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-03-10 10:16:27 +0100 |
commit | d037c5019d51b9fc64690f5e73158c1dd683012b (patch) | |
tree | 8127bde97d30278f53d99de32c1e568c28e1320e | |
parent | ebb2acb89053eca6063ad3b99a3b83cf80d09bca (diff) | |
download | pandoc-d037c5019d51b9fc64690f5e73158c1dd683012b.tar.gz |
Add Muse writer (#3489)
* Add Muse writer
* Advertise new Muse writer
* Muse writer: add regressions tests
-rw-r--r-- | README.md | 3 | ||||
-rw-r--r-- | data/templates/default.muse | 44 | ||||
-rw-r--r-- | deb/control.in | 2 | ||||
-rw-r--r-- | pandoc.cabal | 7 | ||||
-rw-r--r-- | src/Text/Pandoc.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Muse.hs | 336 | ||||
-rw-r--r-- | test/Tests/Old.hs | 3 | ||||
-rw-r--r-- | test/Tests/Writers/Muse.hs | 273 | ||||
-rw-r--r-- | test/tables.muse | 46 | ||||
-rw-r--r-- | test/test-pandoc.hs | 2 | ||||
-rw-r--r-- | test/writer.muse | 772 | ||||
-rw-r--r-- | trypandoc/index.html | 1 |
12 files changed, 1489 insertions, 3 deletions
@@ -26,7 +26,7 @@ write plain text, [Markdown], [CommonMark], [PHP Markdown Extra], [DocBook], [OpenDocument], [ODT], [Word docx], [GNU Texinfo], [MediaWiki markup], [DokuWiki markup], [ZimWiki markup], [Haddock markup], [EPUB] \(v2 or v3\), [FictionBook2], [Textile], [groff man] pages, -[Emacs Org mode], [AsciiDoc], [InDesign ICML], [TEI Simple], and [Slidy], +[Emacs Org mode], [AsciiDoc], [InDesign ICML], [TEI Simple], [Muse], 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. @@ -97,6 +97,7 @@ Markdown can be expected to be lossy. [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 +[Muse]: https://amusewiki.org/library/manual diff --git a/data/templates/default.muse b/data/templates/default.muse new file mode 100644 index 000000000..05534adef --- /dev/null +++ b/data/templates/default.muse @@ -0,0 +1,44 @@ +$if(author)$ +#author $author$ +$endif$ +$if(title)$ +#title $title$ +$endif$ +$if(lang)$ +#lang $lang$ +$endif$ +$if(LISTtitle)$ +#LISTtitle $LISTtitle$ +$endif$ +$if(subtitle)$ +#subtitle $subtitle$ +$endif$ +$if(SORTauthors)$ +#SORTauthors $SORTauthors$ +$endif$ +$if(SORTtopics)$ +#SORTtopics $SORTtopics$ +$endif$ +$if(date)$ +#date $date$ +$endif$ +$if(notes)$ +#notes $notes$ +$endif$ +$if(source)$ +#source $source$ +$endif$ + +$for(header-includes)$ +$header-includes$ + +$endfor$ +$for(include-before)$ +$include-before$ + +$endfor$ +$body$ +$for(include-after)$ + +$include-after$ +$endfor$ diff --git a/deb/control.in b/deb/control.in index 549f9c115..d1aa865ce 100644 --- a/deb/control.in +++ b/deb/control.in @@ -16,5 +16,5 @@ Description: general markup converter Docbook, OPML, OpenDocument, ODT, Word docx, RTF, MediaWiki, DokuWiki, Textile, groff man pages, plain text, Emacs Org-Mode, AsciiDoc, Haddock markup, EPUB (v2 and v3), FictionBook2, - InDesign ICML, and several kinds of HTML/javascript + InDesign ICML, Muse, and several kinds of HTML/javascript slide shows (S5, Slidy, Slideous, DZSlides, reveal.js). diff --git a/pandoc.cabal b/pandoc.cabal index 8a3995fd0..b0be28c33 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -24,7 +24,7 @@ Description: Pandoc is a Haskell library for converting from one markup Word docx, RTF, MediaWiki, DokuWiki, ZimWiki, Textile, groff man pages, plain text, Emacs Org-Mode, AsciiDoc, Haddock markup, EPUB (v2 and v3), FictionBook2, InDesign ICML, - and several kinds of HTML/javascript slide shows (S5, Slidy, + Muse, and several kinds of HTML/javascript slide shows (S5, Slidy, Slideous, DZSlides, reveal.js). . In contrast to most existing tools for converting Markdown @@ -50,6 +50,7 @@ Data-Files: data/templates/default.texinfo data/templates/default.man data/templates/default.markdown + data/templates/default.muse data/templates/default.commonmark data/templates/default.rst data/templates/default.plain @@ -169,6 +170,7 @@ Extra-Source-Files: test/tables.rtf test/tables.txt test/tables.fb2 + test/tables.muse test/testsuite.txt test/writer.latex test/writer.context @@ -194,6 +196,7 @@ Extra-Source-Files: test/writer.opml test/writer.dokuwiki test/writer.zimwiki + test/writer.muse test/writers-lang-and-dir.latex test/writers-lang-and-dir.context test/dokuwiki_inline_formatting.dokuwiki @@ -389,6 +392,7 @@ Library Text.Pandoc.Writers.EPUB, Text.Pandoc.Writers.FB2, Text.Pandoc.Writers.TEI, + Text.Pandoc.Writers.Muse, Text.Pandoc.Writers.Math, Text.Pandoc.Writers.Shared, Text.Pandoc.PDF, @@ -540,6 +544,7 @@ Test-Suite test-pandoc Tests.Writers.Docx Tests.Writers.RST Tests.Writers.TEI + Tests.Writers.Muse Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind -threaded Default-Language: Haskell98 diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 5561c719d..1577491df 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -136,6 +136,7 @@ module Text.Pandoc , writeCommonMark , writeCustom , writeTEI + , writeMuse -- * Rendering templates and default templates , module Text.Pandoc.Templates -- * Miscellaneous @@ -191,6 +192,7 @@ import Text.Pandoc.Writers.LaTeX import Text.Pandoc.Writers.Man import Text.Pandoc.Writers.Markdown import Text.Pandoc.Writers.MediaWiki +import Text.Pandoc.Writers.Muse import Text.Pandoc.Writers.Native import Text.Pandoc.Writers.ODT import Text.Pandoc.Writers.OpenDocument @@ -307,6 +309,7 @@ writers = [ ,("haddock" , StringWriter writeHaddock) ,("commonmark" , StringWriter writeCommonMark) ,("tei" , StringWriter writeTEI) + ,("muse" , StringWriter writeMuse) ] getDefaultExtensions :: String -> Extensions diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs new file mode 100644 index 000000000..cc88eb762 --- /dev/null +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -0,0 +1,336 @@ +{-# LANGUAGE OverloadedStrings #-} +{- +Copyright (C) 2017 Alexander Krotov <ilabdsf@gmail.com> + +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.Muse + Copyright : Copyright (C) 2017 Alexander Krotov + License : GNU GPL, version 2 or above + + Maintainer : Alexander Krotov <ilabdsf@gmail.com> + Stability : stable + Portability : portable + +Conversion of 'Pandoc' documents to Muse. + +This module is mostly intended for <https://amusewiki.org/ Amusewiki> markup support, +as described by <https://amusewiki.org/library/manual Text::Amuse markup manual>. +Original <https://www.gnu.org/software/emacs-muse/ Emacs Muse> markup support +is a secondary goal. + +Where Text::Amuse markup +<https://metacpan.org/pod/Text::Amuse#DIFFERENCES-WITH-THE-ORIGINAL-EMACS-MUSE-MARKUP differs> +from <https://www.gnu.org/software/emacs-muse/manual/ Emacs Muse markup>, +Text::Amuse markup is supported. +For example, native tables are always used instead of Org Mode tables. +However, @\<literal style="html">@ tag is used for HTML raw blocks +even though it is supported only in Emacs Muse. +-} +module Text.Pandoc.Writers.Muse (writeMuse) where +import Control.Monad.State +import Data.List (intersperse, transpose, isInfixOf) +import System.FilePath (takeExtension) +import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Definition +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 + +type Notes = [[Block]] +data WriterState = + WriterState { stNotes :: Notes + , stOptions :: WriterOptions + , stTopLevel :: Bool + , stInsideBlock :: Bool + } + +-- | Convert Pandoc to Muse. +writeMuse :: PandocMonad m + => WriterOptions + -> Pandoc + -> m String +writeMuse opts document = + let st = WriterState { stNotes = [] + , stOptions = opts + , stTopLevel = True + , stInsideBlock = False + } + in evalStateT (pandocToMuse document) st + +-- | Return Muse representation of document. +pandocToMuse :: PandocMonad m + => Pandoc + -> StateT WriterState m String +pandocToMuse (Pandoc meta blocks) = do + opts <- gets stOptions + let colwidth = if writerWrapText opts == WrapAuto + then Just $ writerColumns opts + else Nothing + metadata <- metaToJSON opts + (fmap (render colwidth) . blockListToMuse) + (fmap (render colwidth) . inlineListToMuse) + meta + body <- blockListToMuse blocks + notes <- liftM (reverse . stNotes) get >>= notesToMuse + let main = render colwidth $ body $+$ notes + let context = defField "body" main + $ metadata + case writerTemplate opts of + Nothing -> return main + Just tpl -> return $ renderTemplate' tpl context + +-- | Convert list of Pandoc block elements to Muse. +blockListToMuse :: PandocMonad m + => [Block] -- ^ List of block elements + -> StateT WriterState m Doc +blockListToMuse blocks = do + oldState <- get + modify $ \s -> s { stTopLevel = not $ stInsideBlock s + , stInsideBlock = True + } + contents <- mapM blockToMuse blocks + modify $ \s -> s { stTopLevel = stTopLevel oldState + , stInsideBlock = stInsideBlock oldState + } + return $ cat contents + +-- | Convert Pandoc block element to Muse. +blockToMuse :: PandocMonad m + => Block -- ^ Block element + -> StateT WriterState m Doc +blockToMuse (Plain inlines) = inlineListToMuse inlines +blockToMuse (Para inlines) = do + contents <- inlineListToMuse inlines + return $ contents <> blankline +blockToMuse (LineBlock lns) = do + let splitStanza [] = [] + splitStanza xs = case break (== mempty) xs of + (l, []) -> l : [] + (l, _:r) -> l : splitStanza r + let joinWithLinefeeds = nowrap . mconcat . intersperse cr + let joinWithBlankLines = mconcat . intersperse blankline + let prettyfyStanza ls = joinWithLinefeeds <$> mapM inlineListToMuse ls + contents <- joinWithBlankLines <$> mapM prettyfyStanza (splitStanza lns) + return $ blankline $$ "<verse>" $$ contents $$ "</verse>" <> blankline +blockToMuse (CodeBlock (_,_,_) str) = do + return $ "<example>" $$ text str $$ "</example>" $$ blankline +blockToMuse (RawBlock (Format format) str) = + return $ blankline $$ "<literal style=\"" <> text format <> "\">" $$ + text str $$ "</literal>" $$ blankline +blockToMuse (BlockQuote blocks) = do + contents <- blockListToMuse blocks + return $ blankline + <> "<quote>" + $$ flush contents -- flush to drop blanklines + $$ "</quote>" + <> blankline +blockToMuse (OrderedList (start, style, _) items) = do + let markers = take (length items) $ orderedListMarkers + (start, style, Period) + let maxMarkerLength = maximum $ map length markers + let markers' = map (\m -> let s = maxMarkerLength - length m + in m ++ replicate s ' ') markers + contents <- mapM (\(item, num) -> orderedListItemToMuse item num) $ + zip markers' items + -- ensure that sublists have preceding blank line + topLevel <- gets stTopLevel + return $ cr $$ ((if topLevel then nest 1 else id) $ vcat contents) $$ blankline + where orderedListItemToMuse :: PandocMonad m + => String -- ^ marker for list item + -> [Block] -- ^ list item (list of blocks) + -> StateT WriterState m Doc + orderedListItemToMuse marker item = do + contents <- blockListToMuse item + return $ hang (length marker + 1) (text marker <> space) contents +blockToMuse (BulletList items) = do + contents <- mapM bulletListItemToMuse items + -- ensure that sublists have preceding blank line + topLevel <- gets stTopLevel + return $ cr $$ ((if topLevel then nest 1 else id) $ vcat contents) $$ blankline + where bulletListItemToMuse :: PandocMonad m + => [Block] + -> StateT WriterState m Doc + bulletListItemToMuse item = do + contents <- blockListToMuse item + return $ hang 2 "- " contents +blockToMuse (DefinitionList items) = do + contents <- mapM definitionListItemToMuse items + return $ cr $$ (nest 1 $ vcat $ contents) $$ blankline + where definitionListItemToMuse :: PandocMonad m + => ([Inline], [[Block]]) + -> StateT WriterState m Doc + definitionListItemToMuse (label, defs) = do + label' <- inlineListToMuse label + contents <- liftM vcat $ mapM blockListToMuse defs + let label'' = label' <> " :: " + let ind = offset label'' + return $ hang ind label'' contents +blockToMuse (Header level (ident,_,_) inlines) = do + contents <- inlineListToMuse inlines + let attr' = if null ident + then empty + else "#" <> text ident <> cr + let header' = text $ replicate level '*' + return $ blankline <> nowrap (header' <> space <> contents) + <> blankline <> attr' +-- https://www.gnu.org/software/emacs-muse/manual/muse.html#Horizontal-Rules-and-Anchors +blockToMuse HorizontalRule = return $ blankline $$ "----" $$ blankline +blockToMuse (Table caption _ _ headers rows) = do + caption' <- inlineListToMuse caption + headers' <- mapM blockListToMuse headers + rows' <- mapM (mapM blockListToMuse) rows + let noHeaders = all null headers + + let numChars = maximum . map offset + -- FIXME: width is not being used. + let widthsInChars = + map numChars $ transpose (headers' : rows') + -- FIXME: Muse doesn't allow blocks with height more than 1. + let hpipeBlocks sep blocks = hcat $ intersperse sep' blocks + where h = maximum (1 : map height blocks) + sep' = lblock (length sep) $ vcat (map text $ replicate h sep) + let makeRow sep = hpipeBlocks sep . zipWith lblock widthsInChars + let head' = makeRow " || " headers' + let rowSeparator = if noHeaders then " | " else " | " + rows'' <- mapM (\row -> do cols <- mapM blockListToMuse row + return $ makeRow rowSeparator cols) rows + let body = vcat rows'' + return $ (if noHeaders then empty else head') + $$ body + $$ (if null caption then empty else "|+ " <> caption' <> " +|") + $$ blankline +blockToMuse (Div _ bs) = blockListToMuse bs +blockToMuse Null = return empty + +-- | Return Muse representation of notes. +notesToMuse :: PandocMonad m + => Notes + -> StateT WriterState m Doc +notesToMuse notes = + mapM (\(num, note) -> noteToMuse num note) (zip [1..] notes) >>= + return . vsep + +-- | Return Muse representation of a note. +noteToMuse :: PandocMonad m + => Int + -> [Block] + -> StateT WriterState m Doc +noteToMuse num note = do + contents <- blockListToMuse note + let marker = "[" ++ show num ++ "] " + return $ hang (length marker) (text marker) contents + +-- | Escape special characters for Muse. +escapeString :: String -> String +escapeString s = + "<verbatim>" ++ + substitute "</verbatim>" "<</verbatim><verbatim>/verbatim>" s ++ + "</verbatim>" + +-- | Escape special characters for Muse if needed. +conditionalEscapeString :: String -> String +conditionalEscapeString s + | any (`elem` ("*<=>[]|" :: String)) s || + "::" `isInfixOf` s = escapeString s + | otherwise = s + +-- | Convert list of Pandoc inline elements to Muse. +inlineListToMuse :: PandocMonad m + => [Inline] + -> StateT WriterState m Doc +inlineListToMuse lst = mapM inlineToMuse lst >>= return . hcat + +-- | Convert Pandoc inline element to Muse. +inlineToMuse :: PandocMonad m + => Inline + -> StateT WriterState m Doc +inlineToMuse (Str str) = return $ text $ conditionalEscapeString str +inlineToMuse (Emph lst) = do + contents <- inlineListToMuse lst + return $ "<em>" <> contents <> "</em>" +inlineToMuse (Strong lst) = do + contents <- inlineListToMuse lst + return $ "<strong>" <> contents <> "</strong>" +inlineToMuse (Strikeout lst) = do + contents <- inlineListToMuse lst + return $ "<del>" <> contents <> "</del>" +inlineToMuse (Superscript lst) = do + contents <- inlineListToMuse lst + return $ "<sup>" <> contents <> "</sup>" +inlineToMuse (Subscript lst) = do + contents <- inlineListToMuse lst + return $ "<sub>" <> contents <> "</sub>" +inlineToMuse (SmallCaps lst) = inlineListToMuse lst +inlineToMuse (Quoted SingleQuote lst) = do + contents <- inlineListToMuse lst + return $ "'" <> contents <> "'" +inlineToMuse (Quoted DoubleQuote lst) = do + contents <- inlineListToMuse lst + return $ "\"" <> contents <> "\"" +-- Amusewiki does not support <cite> tag, +-- and Emacs Muse citation support is limited +-- (https://www.gnu.org/software/emacs-muse/manual/html_node/Citations.html#Citation) +-- so just fallback to expanding inlines. +inlineToMuse (Cite _ lst) = inlineListToMuse lst +inlineToMuse (Code _ str) = return $ + "<code>" <> text (conditionalEscapeString str) <> "</code>" +inlineToMuse (Math InlineMath str) = + lift (texMathToInlines InlineMath str) >>= inlineListToMuse +inlineToMuse (Math DisplayMath str) = do + contents <- lift (texMathToInlines DisplayMath str) >>= inlineListToMuse + return $ "<verse>" <> contents <> "</verse>" <> blankline +inlineToMuse (RawInline (Format f) str) = + return $ "<literal style=\"" <> text f <> "\">" <> text str <> "</literal>" +inlineToMuse LineBreak = return $ "<br>" <> cr +inlineToMuse Space = return space +inlineToMuse SoftBreak = do + wrapText <- gets $ writerWrapText . stOptions + return $ if wrapText == WrapPreserve then cr else space +inlineToMuse (Link _ txt (src, _)) = do + case txt of + [Str x] | escapeURI x == src -> + return $ "[[" <> text (escapeLink x) <> "]]" + _ -> do contents <- inlineListToMuse txt + return $ "[[" <> text (escapeLink src) <> "][" <> contents <> "]]" + where escapeLink lnk = escapeURI (if isImageUrl lnk then "URL:" ++ lnk else lnk) + -- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el + imageExtensions = [".eps", ".gif", ".jpg", ".jpeg", ".pbm", ".png", ".tiff", ".xbm", ".xpm"] + isImageUrl = (`elem` imageExtensions) . takeExtension +inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) = + inlineToMuse (Image attr alt (source,title)) +inlineToMuse (Image _ inlines (source, title)) = do + alt <- inlineListToMuse inlines + let title' = if null title + then if null inlines + then "" + else "[" <> alt <> "]" + else "[" <> text title <> "]" + return $ "[[" <> text source <> "]" <> title' <> "]" +inlineToMuse (Note contents) = do + -- add to notes in state + notes <- gets stNotes + modify $ \st -> st { stNotes = contents:notes } + let ref = show $ (length notes) + 1 + return $ "[" <> text ref <> "]" +inlineToMuse (Span (_,name:_,_) inlines) = do + contents <- inlineListToMuse inlines + return $ "<class name=\"" <> text name <> "\">" <> contents <> "</class>" +inlineToMuse (Span _ lst) = inlineListToMuse lst diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index 253238d21..d8cd3f5a0 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -142,6 +142,9 @@ tests = [ testGroup "markdown" , test "context" ["-f", "native", "-t", "context", "-s"] "writers-lang-and-dir.native" "writers-lang-and-dir.context" ] + , testGroup "muse" + [ testGroup "writer" $ writerTests "muse" + ] ] -- makes sure file is fully closed after reading diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs new file mode 100644 index 000000000..12ecfb477 --- /dev/null +++ b/test/Tests/Writers/Muse.hs @@ -0,0 +1,273 @@ +module Tests.Writers.Muse (tests) where + +import Test.Framework +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary() +import Text.Pandoc.Builder + +muse :: (ToPandoc a) => a -> String +muse = museWithOpts def{ writerWrapText = WrapNone } + +museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +museWithOpts opts = purely (writeMuse opts) . toPandoc + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test muse + +tests :: [Test] +tests = [ testGroup "block elements" + [ "plain" =: plain (text "Foo bar.") =?> "Foo bar." + , testGroup "paragraphs" + [ "single paragraph" =: para (text "Sample paragraph.") + =?> "Sample paragraph." + , "two paragraphs" =: para (text "First paragraph.") <> + para (text "Second paragraph.") + =?> unlines [ "First paragraph." + , "" + , "Second paragraph." + ] + ] + , "line block" =: lineBlock ([text "Foo", text "bar", text "baz"]) + =?> unlines [ "<verse>" + , "Foo" + , "bar" + , "baz" + , "</verse>" + ] + , "code block" =: codeBlock ("int main(void) {\n\treturn 0;\n}") + =?> unlines [ "<example>" + , "int main(void) {" + , "\treturn 0;" + , "}" + , "</example>" + ] + , "html raw block" =: rawBlock "html" "<hr>" + =?> unlines [ "<literal style=\"html\">" + , "<hr>" + , "</literal>" + ] + , "block quote" =: blockQuote (para (text "Foo")) + =?> unlines [ "<quote>" + , "Foo" + , "</quote>" + ] + , testGroup "lists" + [ testGroup "simple lists" + [ + "ordered list" =: orderedList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> unlines [ " 1. first" + , " 2. second" + , " 3. third" + ] + , "ordered list with Roman numerals" + =: orderedListWith (1, UpperRoman, DefaultDelim) + [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> unlines [ " I. first" + , " II. second" + , " III. third" + ] + , "bullet list" =: bulletList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> unlines [ " - first" + , " - second" + , " - third" + ] + , "definition list" =: definitionList [ (text "first definition", [plain $ text "first description"]) + , (text "second definition", [plain $ text "second description"]) + , (text "third definition", [plain $ text "third description"]) + ] + =?> unlines [ " first definition :: first description" + , " second definition :: second description" + , " third definition :: third description" + ] + ] + , testGroup "nested lists" + [ "nested ordered list" =: orderedList [ plain $ text "First outer" + , plain (text "Second outer:") <> + orderedList [ plain $ text "first" + , plain $ text "second" + ] + , plain $ text "Third outer" + ] + =?> unlines [ " 1. First outer" + , " 2. Second outer:" + , " 1. first" + , " 2. second" + , " 3. Third outer" + ] + , "nested bullet lists" =: bulletList [ plain $ text "First outer" + , plain (text "Second outer:") <> + bulletList [ plain $ text "first" + , plain $ text "second" + ] + , plain $ text "Third outer" + ] + =?> unlines [ " - First outer" + , " - Second outer:" + , " - first" + , " - second" + , " - Third outer" + ] + , "nested definition lists" =: definitionList [ (text "first definition", [plain $ text "first description"]) + , (text "second definition", + [ plain (text "second description") + , definitionList [ ( text "first inner definition" + , [plain $ text "first inner description"]) + , ( text "second inner definition" + , [plain $ text "second inner description"]) + ] + ] + ) + ] + =?> unlines [ " first definition :: first description" + , " second definition :: second description" + , " first inner definition :: first inner description" + , " second inner definition :: second inner description" + ] + ] + ] + , testGroup "headings" + [ "normal heading" =: + header 1 (text "foo") =?> "* foo" + , "heading levels" =: + header 1 (text "First level") <> + header 3 (text "Third level") =?> + unlines [ "* First level" + , "" + , "*** Third level" + ] + ] + , "horizontal rule" =: horizontalRule =?> "----" + , testGroup "tables" + [ "table without header" =: + let rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] + ,[para $ text "Para 2.1", para $ text "Para 2.2"]] + in simpleTable [] rows + =?> + unlines [ "Para 1.1 | Para 1.2" + , "Para 2.1 | Para 2.2" + ] + , "table with header" =: + let headers = [plain $ text "header 1", plain $ text "header 2"] + rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] + ,[para $ text "Para 2.1", para $ text "Para 2.2"]] + in simpleTable headers rows + =?> + unlines [ "header 1 || header 2" + , "Para 1.1 | Para 1.2" + , "Para 2.1 | Para 2.2" + ] + , "table with header and caption" =: + let caption = text "Table 1" + headers = [plain $ text "header 1", plain $ text "header 2"] + rows = [[para $ text "Para 1.1", para $ text "Para 1.2"] + ,[para $ text "Para 2.1", para $ text "Para 2.2"]] + in table caption mempty headers rows + =?> unlines [ "header 1 || header 2" + , "Para 1.1 | Para 1.2" + , "Para 2.1 | Para 2.2" + , "|+ Table 1 +|" + ] + ] + -- Div is trivial + -- Null is trivial + ] + , testGroup "inline elements" + [ testGroup "string" + [ "string" =: str "foo" =?> "foo" + , "escape footnote" =: str "[1]" =?> "<verbatim>[1]</verbatim>" + , "escape verbatim close tag" =: str "foo</verbatim>bar" + =?> "<verbatim>foo<</verbatim><verbatim>/verbatim>bar</verbatim>" + , "escape pipe to avoid accidental tables" =: str "foo | bar" + =?> "<verbatim>foo | bar</verbatim>" + , "escape definition list markers" =: str "::" =?> "<verbatim>::</verbatim>" + -- We don't want colons to be escaped if they can't be confused + -- with definition list item markers. + , "do not escape colon" =: str ":" =?> ":" + ] + , testGroup "emphasis" + [ "emph" =: emph (text "foo") =?> "<em>foo</em>" + , "strong" =: strong (text "foo") =?> "<strong>foo</strong>" + , "strikeout" =: strikeout (text "foo") =?> "<del>foo</del>" + ] + , "superscript" =: superscript (text "foo") =?> "<sup>foo</sup>" + , "subscript" =: subscript (text "foo") =?> "<sub>foo</sub>" + , "smallcaps" =: smallcaps (text "foo") =?> "foo" + , "single quoted" =: singleQuoted (text "foo") =?> "'foo'" + , "double quoted" =: doubleQuoted (text "foo") =?> "\"foo\"" + -- Cite is trivial + , testGroup "code" + [ "simple" =: code "foo" =?> "<code>foo</code>" + , "escape lightweight markup" =: code "foo = bar" =?> "<code><verbatim>foo = bar</verbatim></code>" + , "escape tag" =: code "<code>foo = bar</code> baz" =?> "<code><verbatim><code>foo = bar</code> baz</verbatim></code>" + ] + , testGroup "spaces" + [ "space" =: text "a" <> space <> text "b" =?> "a b" + , "soft break" =: text "a" <> softbreak <> text "b" =?> "a b" + , test (museWithOpts def{ writerWrapText = WrapPreserve }) + "preserve soft break" $ text "a" <> softbreak <> text "b" + =?> "a\nb" + , "line break" =: text "a" <> linebreak <> text "b" =?> "a<br>\nb" + ] + , testGroup "math" + [ "inline math" =: math "2^3" =?> "2<sup>3</sup>" + , "display math" =: displayMath "2^3" =?> "<verse>2<sup>3</sup></verse>" + ] + , "raw inline" + =: rawInline "html" "<mark>marked text</mark>" + =?> "<literal style=\"html\"><mark>marked text</mark></literal>" + , testGroup "links" + [ "link with description" =: link "https://example.com" "" (str "Link 1") + =?> "[[https://example.com][Link 1]]" + , "link without description" =: link "https://example.com" "" (str "https://example.com") + =?> "[[https://example.com]]" + -- Internal links in Muse include '#' + , "link to anchor" =: link "#intro" "" (str "Introduction") + =?> "[[#intro][Introduction]]" + -- According to Emacs Muse manual, links to images should be prefixed with "URL:" + , "link to image with description" =: link "1.png" "" (str "Link to image") + =?> "[[URL:1.png][Link to image]]" + , "link to image without description" =: link "1.png" "" (str "1.png") + =?> "[[URL:1.png]]" + ] + , "image" =: image "image.png" "Image 1" (str "") =?> "[[image.png][Image 1]]" + , "note" =: note (plain (text "Foo")) + =?> unlines [ "[1]" + , "" + , "[1] Foo" + ] + , "span" =: spanWith ("",["foobar"],[]) (str "Some text") + =?> "<class name=\"foobar\">Some text</class>" + , testGroup "combined" + [ "emph word before" =: + para (text "foo" <> emph (text "bar")) =?> + "foo<em>bar</em>" + , "emph word after" =: + para (emph (text "foo") <> text "bar") =?> + "<em>foo</em>bar" + , "emph quoted" =: + para (doubleQuoted (emph (text "foo"))) =?> + "\"<em>foo</em>\"" + , "strong word before" =: + para (text "foo" <> strong (text "bar")) =?> + "foo<strong>bar</strong>" + , "strong word after" =: + para (strong (text "foo") <> text "bar") =?> + "<strong>foo</strong>bar" + , "strong quoted" =: + para (singleQuoted (strong (text "foo"))) =?> + "'<strong>foo</strong>'" + ] + ] + ] diff --git a/test/tables.muse b/test/tables.muse new file mode 100644 index 000000000..afdccd476 --- /dev/null +++ b/test/tables.muse @@ -0,0 +1,46 @@ +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 bfad1ab3d..e8575e664 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -29,6 +29,7 @@ import qualified Tests.Writers.Org import qualified Tests.Writers.Plain import qualified Tests.Writers.RST import qualified Tests.Writers.TEI +import qualified Tests.Writers.Muse import Text.Pandoc.Shared (inDirectory) tests :: [Test] @@ -48,6 +49,7 @@ tests = [ Tests.Command.tests , testGroup "Docx" Tests.Writers.Docx.tests , testGroup "RST" Tests.Writers.RST.tests , testGroup "TEI" Tests.Writers.TEI.tests + , testGroup "Muse" Tests.Writers.Muse.tests ] , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests diff --git a/test/writer.muse b/test/writer.muse new file mode 100644 index 000000000..c19cb8ab2 --- /dev/null +++ b/test/writer.muse @@ -0,0 +1,772 @@ +#author John MacFarlane +#title Pandoc Test Suite +#date July 17, 2006 + +This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +markdown test suite. + +---- + +* Headers + +#headers + +** Level 2 with an [[/url][embedded link]] + +#level-2-with-an-embedded-link + +*** Level 3 with <em>emphasis</em> + +#level-3-with-emphasis + +**** Level 4 + +#level-4 + +***** Level 5 + +#level-5 + +* Level 1 + +#level-1 + +** Level 2 with <em>emphasis</em> + +#level-2-with-emphasis + +*** Level 3 + +#level-3 +with no blank line + +** Level 2 + +#level-2 +with no blank line + +---- + +* 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. <verbatim>*</verbatim> criminey. + +There should be a hard line break<br> +here. + +---- + +* Block Quotes + +#block-quotes +E-mail style: + +<quote> +This is a block quote. It is pretty short. +</quote> + +<quote> +Code in a block quote: + +<example> +sub status { + print "working"; +} +</example> + +A list: + +1. item one +2. item two + +Nested block quotes: + +<quote> +nested +</quote> + +<quote> +nested +</quote> +</quote> + +This should not be a block quote: 2 <verbatim>></verbatim> 1. + +And a following paragraph. + +---- + +* Code Blocks + +#code-blocks +Code: + +<example> +---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab +</example> + +And: + +<example> + this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ +</example> + +---- + +* Lists + +#lists + +** 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 + +** 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. + +** 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 + +** 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 + +** 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 + +---- + +* 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: + + <em>apple</em> :: red fruit + + contains seeds, crisp, pleasant to taste + <em>orange</em> :: orange fruit + + <example> + { orange code block } + </example> + + <quote> +orange block quote + </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 + +* HTML Blocks + +#html-blocks +Simple block on one line: + +fooAnd nested without indentation: + +foo + +barInterpreted markdown in a table: + +<literal style="html"> +<table> +</literal> + +<literal style="html"> +<tr> +</literal> + +<literal style="html"> +<td> +</literal> + +This is <em>emphasized</em> + +<literal style="html"> +</td> +</literal> + +<literal style="html"> +<td> +</literal> + +And this is <strong>strong</strong> + +<literal style="html"> +</td> +</literal> + +<literal style="html"> +</tr> +</literal> + +<literal style="html"> +</table> +</literal> + +<literal style="html"> +<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> +</literal> + +Here’s a simple block: + +foo + +This should be a code block, though: + +<example> +<div> + foo +</div> +</example> + +As should this: + +<example> +<div>foo</div> +</example> + +Now, nested: + +fooThis should just be an HTML comment: + +<literal style="html"> +<!-- Comment --> +</literal> + +Multiline: + +<literal style="html"> +<!-- +Blah +Blah +--> +</literal> + +<literal style="html"> +<!-- + This is another comment. +--> +</literal> + +Code block: + +<example> +<!-- Comment --> +</example> + +Just plain comment, with trailing spaces on the line: + +<literal style="html"> +<!-- foo --> +</literal> + +Code: + +<example> +<hr /> +</example> + +Hr’s: + +<literal style="html"> +<hr> +</literal> + +<literal style="html"> +<hr /> +</literal> + +<literal style="html"> +<hr /> +</literal> + +<literal style="html"> +<hr> +</literal> + +<literal style="html"> +<hr /> +</literal> + +<literal style="html"> +<hr /> +</literal> + +<literal style="html"> +<hr class="foo" id="bar" /> +</literal> + +<literal style="html"> +<hr class="foo" id="bar" /> +</literal> + +<literal style="html"> +<hr class="foo" id="bar"> +</literal> + +---- + +* Inline Markup + +#inline-markup +This is <em>emphasized</em>, and so <em>is this</em>. + +This is <strong>strong</strong>, and so <strong>is this</strong>. + +An <em>[[/url][emphasized link]]</em>. + +<strong><em>This is strong and em.</em></strong> + +So is <strong><em>this</em></strong> word. + +<strong><em>This is strong and em.</em></strong> + +So is <strong><em>this</em></strong> word. + +This is code: <code><verbatim>></verbatim></code>, <code>$</code>, +<code>\</code>, <code>\$</code>, <code><verbatim><html></verbatim></code>. + +<del>This is <em>strikeout</em>.</del> + +Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup> +a<sup>hello there</sup>. + +Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O. + +These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d. + +---- + +* 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>code</code>' and a +"[[http://example.com/?foo=1&bar=2][quoted link]]". + +Some dashes: one—two — three—four — five. + +Dashes between numbers: 5–7, 255–66, 1987–1999. + +Ellipses…and…and…. + +---- + +* LaTeX + +#latex + - <literal style="tex">\cite[22-23]{smith.1899}</literal> + - 2 + 2 <verbatim>=</verbatim> 4 + - <em>x</em> ∈ <em>y</em> + - <em>α</em> ∧ <em>ω</em> + - 223 + - <em>p</em>-Tree + - Here’s some display math: + <verse><verbatim>$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</verbatim></verse> + - Here’s one that has a line break in it: + <em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup>. + +These shouldn’t be math: + + - To get the famous equation, write + <code><verbatim>$e = mc^2$</verbatim></code>. + - $22,000 is a <em>lot</em> of money. So is $34,000. (It worked if "lot" is + emphasized.) + - Shoes ($20) and socks ($5). + - Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$. + +Here’s a LaTeX table: + +<literal style="latex"> +\begin{tabular}{|l|l|}\hline +Animal & Number \\ \hline +Dog & 2 \\ +Cat & 1 \\ \hline +\end{tabular} +</literal> + +---- + +* 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 <verbatim><</verbatim> 5. + +6 <verbatim>></verbatim> 5. + +Backslash: \ + +Backtick: ` + +Asterisk: <verbatim>*</verbatim> + +Underscore: _ + +Left brace: { + +Right brace: } + +Left bracket: <verbatim>[</verbatim> + +Right bracket: <verbatim>]</verbatim> + +Left paren: ( + +Right paren: ) + +Greater-than: <verbatim>></verbatim> + +Hash: # + +Period: . + +Bang: ! + +Plus: + + +Minus: - + +---- + +* Links + +#links + +** Explicit + +#explicit +Just a [[/url/][URL]]. + +[[/url/][URL and title]]. + +[[/url/][URL and title]]. + +[[/url/][URL and title]]. + +[[/url/][URL and title]] + +[[/url/][URL and title]] + +[[/url/with_underscore][with_underscore]] + +[[mailto:nobody@nowhere.net][Email link]] + +[[][Empty]]. + +** Reference + +#reference +Foo [[/url/][bar]]. + +Foo [[/url/][bar]]. + +Foo [[/url/][bar]]. + +With [[/url/][embedded <verbatim>[brackets]</verbatim>]]. + +[[/url/][b]] by itself should be a link. + +Indented [[/url][once]]. + +Indented [[/url][twice]]. + +Indented [[/url][thrice]]. + +This should <verbatim>[not][]</verbatim> be a link. + +<example> +[not]: /url +</example> + +Foo [[/url/][bar]]. + +Foo [[/url/][biz]]. + +** With ampersands + +#with-ampersands +Here’s a [[http://example.com/?foo=1&bar=2][link with an ampersand in the +URL]]. + +Here’s a link with an amersand in the link text: [[http://att.com/][AT&T]]. + +Here’s an [[/script?foo=1&bar=2][inline link]]. + +Here’s an [[/script?foo=1&bar=2][inline link in pointy braces]]. + +** Autolinks + +#autolinks +With an ampersand: [[http://example.com/?foo=1&bar=2]] + + - In a list? + - [[http://example.com/]] + - It should. + +An e-mail address: [[mailto:nobody@nowhere.net][nobody@nowhere.net]] + +<quote> +Blockquoted: [[http://example.com/]] +</quote> + +Auto-links should not occur here: +<code><verbatim><http://example.com/></verbatim></code> + +<example> +or here: <http://example.com/> +</example> + +---- + +* Images + +#images +From "Voyage dans la Lune" by Georges Melies (1902): + +[[lalune.jpg][Voyage dans la Lune]] + +Here is a movie [[movie.jpg][movie]] icon. + +---- + +* Footnotes + +#footnotes +Here is a footnote reference,[1] and another.[2] This should <em>not</em> be a +footnote reference, because it contains a <verbatim>space.[^my</verbatim> +<verbatim>note]</verbatim> Here is an inline note.[3] + +<quote> +Notes can go in quotes.[4] +</quote> + + 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). + + <example> + { <code> } + </example> + + 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 <em>easier</em> to type. Inline notes may contain + [[http://google.com][links]] and <code><verbatim>]</verbatim></code> + verbatim characters, as well as <verbatim>[bracketed</verbatim> + <verbatim>text].</verbatim> + +[4] In quote. + +[5] In list. diff --git a/trypandoc/index.html b/trypandoc/index.html index d9674793b..26a373112 100644 --- a/trypandoc/index.html +++ b/trypandoc/index.html @@ -129,6 +129,7 @@ $(document).ready(function() { <option value="slideous">Slideous</option> <option value="slidy">Slidy</option> <option value="texinfo">Texinfo</option> + <option value="muse">Muse</option> </select> <br/> <pre id="results"></pre> |