From 7eded47bcdd10d1e32125121c7b84f952b1a326e Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Sun, 14 Jul 2013 13:40:27 +0100 Subject: Initial work to create dokuwiki writer (#386) In this first version, all dokuwiki files are straight copies of the media wiki counterparts. --- src/Text/Pandoc/Writers/DokuWiki.hs | 407 ++++++++++++++++++++++++++++++++++++ 1 file changed, 407 insertions(+) create mode 100644 src/Text/Pandoc/Writers/DokuWiki.hs (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs new file mode 100644 index 000000000..b3483adf2 --- /dev/null +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -0,0 +1,407 @@ +{- +Copyright (C) 2008-2010 John MacFarlane + +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.DokuWiki + Copyright : Copyright (C) 2008-2010 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' documents to DokuWiki markup. + +DokuWiki: +-} +module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where +import Text.Pandoc.Definition +import Text.Pandoc.Options +import Text.Pandoc.Shared +import Text.Pandoc.Writers.Shared +import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.XML ( escapeStringForXML ) +import Data.List ( intersect, intercalate ) +import Network.URI ( isURI ) +import Control.Monad.State + +data WriterState = WriterState { + stNotes :: Bool -- True if there are notes + , stListLevel :: [Char] -- String at beginning of list items, e.g. "**" + , stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list + } + +-- | Convert Pandoc to DokuWiki. +writeDokuWiki :: WriterOptions -> Pandoc -> String +writeDokuWiki opts document = + evalState (pandocToDokuWiki opts document) + (WriterState { stNotes = False, stListLevel = [], stUseTags = False }) + +-- | Return DokuWiki representation of document. +pandocToDokuWiki :: WriterOptions -> Pandoc -> State WriterState String +pandocToDokuWiki opts (Pandoc meta blocks) = do + metadata <- metaToJSON opts + (fmap trimr . blockListToDokuWiki opts) + (inlineListToDokuWiki opts) + meta + body <- blockListToDokuWiki opts blocks + notesExist <- get >>= return . stNotes + let notes = if notesExist + then "\n" + else "" + let main = body ++ notes + let context = defField "body" main + $ defField "toc" (writerTableOfContents opts) + $ metadata + if writerStandalone opts + then return $ renderTemplate' (writerTemplate opts) context + else return main + +-- | Escape special characters for DokuWiki. +escapeString :: String -> String +escapeString = escapeStringForXML + +-- | Convert Pandoc block element to DokuWiki. +blockToDokuWiki :: WriterOptions -- ^ Options + -> Block -- ^ Block element + -> State WriterState String + +blockToDokuWiki _ Null = return "" + +blockToDokuWiki opts (Plain inlines) = + inlineListToDokuWiki opts inlines + +-- title beginning with fig: indicates that the image is a figure +blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do + capt <- if null txt + then return "" + else ("|caption " ++) `fmap` inlineListToDokuWiki opts txt + let opt = if null txt + then "" + else "|alt=" ++ if null tit then capt else tit ++ capt + return $ "[[Image:" ++ src ++ "|frame|none" ++ opt ++ "]]\n" + +blockToDokuWiki opts (Para inlines) = do + useTags <- get >>= return . stUseTags + listLevel <- get >>= return . stListLevel + contents <- inlineListToDokuWiki opts inlines + return $ if useTags + then "

" ++ contents ++ "

" + else contents ++ if null listLevel then "\n" else "" + +blockToDokuWiki _ (RawBlock "mediawiki" str) = return str +blockToDokuWiki _ (RawBlock "html" str) = return str +blockToDokuWiki _ (RawBlock _ _) = return "" + +blockToDokuWiki _ HorizontalRule = return "\n-----\n" + +blockToDokuWiki opts (Header level _ inlines) = do + contents <- inlineListToDokuWiki opts inlines + let eqs = replicate level '=' + return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n" + +blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do + let at = classes `intersect` ["actionscript", "ada", "apache", "applescript", "asm", "asp", + "autoit", "bash", "blitzbasic", "bnf", "c", "c_mac", "caddcl", "cadlisp", "cfdg", "cfm", + "cpp", "cpp-qt", "csharp", "css", "d", "delphi", "diff", "div", "dos", "eiffel", "fortran", + "freebasic", "gml", "groovy", "html4strict", "idl", "ini", "inno", "io", "java", "java5", + "javascript", "latex", "lisp", "lua", "matlab", "mirc", "mpasm", "mysql", "nsis", "objc", + "ocaml", "ocaml-brief", "oobas", "oracle8", "pascal", "perl", "php", "php-brief", "plsql", + "python", "qbasic", "rails", "reg", "robots", "ruby", "sas", "scheme", "sdlbasic", + "smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl", + "visualfoxpro", "winbatch", "xml", "xpp", "z80"] + let (beg, end) = if null at + then ("" else " class=\"" ++ unwords classes ++ "\">", "") + else ("", "") + return $ beg ++ escapeString str ++ end + +blockToDokuWiki opts (BlockQuote blocks) = do + contents <- blockListToDokuWiki opts blocks + return $ "
" ++ contents ++ "
" + +blockToDokuWiki opts (Table capt aligns widths headers rows') = do + let alignStrings = map alignmentToString aligns + captionDoc <- if null capt + then return "" + else do + c <- inlineListToDokuWiki opts capt + return $ "" ++ c ++ "\n" + let percent w = show (truncate (100*w) :: Integer) ++ "%" + let coltags = if all (== 0.0) widths + then "" + else unlines $ map + (\w -> "") widths + head' <- if all null headers + then return "" + else do + hs <- tableRowToDokuWiki opts alignStrings 0 headers + return $ "\n" ++ hs ++ "\n\n" + body' <- zipWithM (tableRowToDokuWiki opts alignStrings) [1..] rows' + return $ "\n" ++ captionDoc ++ coltags ++ head' ++ + "\n" ++ unlines body' ++ "\n
\n" + +blockToDokuWiki opts x@(BulletList items) = do + oldUseTags <- get >>= return . stUseTags + listLevel <- get >>= return . stListLevel + let useTags = oldUseTags || not (isSimpleList x) + if useTags + then do + modify $ \s -> s { stUseTags = True } + contents <- mapM (listItemToDokuWiki opts) items + modify $ \s -> s { stUseTags = oldUseTags } + return $ "
    \n" ++ vcat contents ++ "
\n" + else do + modify $ \s -> s { stListLevel = stListLevel s ++ "*" } + contents <- mapM (listItemToDokuWiki opts) items + modify $ \s -> s { stListLevel = init (stListLevel s) } + return $ vcat contents ++ if null listLevel then "\n" else "" + +blockToDokuWiki opts x@(OrderedList attribs items) = do + oldUseTags <- get >>= return . stUseTags + listLevel <- get >>= return . stListLevel + let useTags = oldUseTags || not (isSimpleList x) + if useTags + then do + modify $ \s -> s { stUseTags = True } + contents <- mapM (listItemToDokuWiki opts) items + modify $ \s -> s { stUseTags = oldUseTags } + return $ "\n" ++ vcat contents ++ "\n" + else do + modify $ \s -> s { stListLevel = stListLevel s ++ "#" } + contents <- mapM (listItemToDokuWiki opts) items + modify $ \s -> s { stListLevel = init (stListLevel s) } + return $ vcat contents ++ if null listLevel then "\n" else "" + +blockToDokuWiki opts x@(DefinitionList items) = do + oldUseTags <- get >>= return . stUseTags + listLevel <- get >>= return . stListLevel + let useTags = oldUseTags || not (isSimpleList x) + if useTags + then do + modify $ \s -> s { stUseTags = True } + contents <- mapM (definitionListItemToDokuWiki opts) items + modify $ \s -> s { stUseTags = oldUseTags } + return $ "
\n" ++ vcat contents ++ "
\n" + else do + modify $ \s -> s { stListLevel = stListLevel s ++ ";" } + contents <- mapM (definitionListItemToDokuWiki opts) items + modify $ \s -> s { stListLevel = init (stListLevel s) } + return $ vcat contents ++ if null listLevel then "\n" else "" + +-- Auxiliary functions for lists: + +-- | Convert ordered list attributes to HTML attribute string +listAttribsToString :: ListAttributes -> String +listAttribsToString (startnum, numstyle, _) = + let numstyle' = camelCaseToHyphenated $ show numstyle + in (if startnum /= 1 + then " start=\"" ++ show startnum ++ "\"" + else "") ++ + (if numstyle /= DefaultStyle + then " style=\"list-style-type: " ++ numstyle' ++ ";\"" + else "") + +-- | Convert bullet or ordered list item (list of blocks) to DokuWiki. +listItemToDokuWiki :: WriterOptions -> [Block] -> State WriterState String +listItemToDokuWiki opts items = do + contents <- blockListToDokuWiki opts items + useTags <- get >>= return . stUseTags + if useTags + then return $ "
  • " ++ contents ++ "
  • " + else do + marker <- get >>= return . stListLevel + return $ marker ++ " " ++ contents + +-- | Convert definition list item (label, list of blocks) to DokuWiki. +definitionListItemToDokuWiki :: WriterOptions + -> ([Inline],[[Block]]) + -> State WriterState String +definitionListItemToDokuWiki opts (label, items) = do + labelText <- inlineListToDokuWiki opts label + contents <- mapM (blockListToDokuWiki opts) items + useTags <- get >>= return . stUseTags + if useTags + then return $ "
    " ++ labelText ++ "
    \n" ++ + (intercalate "\n" $ map (\d -> "
    " ++ d ++ "
    ") contents) + else do + marker <- get >>= return . stListLevel + return $ marker ++ " " ++ labelText ++ "\n" ++ + (intercalate "\n" $ map (\d -> init marker ++ ": " ++ d) contents) + +-- | True if the list can be handled by simple wiki markup, False if HTML tags will be needed. +isSimpleList :: Block -> Bool +isSimpleList x = + case x of + BulletList items -> all isSimpleListItem items + OrderedList (num, sty, _) items -> all isSimpleListItem items && + num == 1 && sty `elem` [DefaultStyle, Decimal] + DefinitionList items -> all isSimpleListItem $ concatMap snd items + _ -> False + +-- | True if list item can be handled with the simple wiki syntax. False if +-- HTML tags will be needed. +isSimpleListItem :: [Block] -> Bool +isSimpleListItem [] = True +isSimpleListItem [x] = + case x of + Plain _ -> True + Para _ -> True + BulletList _ -> isSimpleList x + OrderedList _ _ -> isSimpleList x + DefinitionList _ -> isSimpleList x + _ -> False +isSimpleListItem [x, y] | isPlainOrPara x = + case y of + BulletList _ -> isSimpleList y + OrderedList _ _ -> isSimpleList y + DefinitionList _ -> isSimpleList y + _ -> False +isSimpleListItem _ = False + +isPlainOrPara :: Block -> Bool +isPlainOrPara (Plain _) = True +isPlainOrPara (Para _) = True +isPlainOrPara _ = False + +-- | Concatenates strings with line breaks between them. +vcat :: [String] -> String +vcat = intercalate "\n" + +-- Auxiliary functions for tables: + +tableRowToDokuWiki :: WriterOptions + -> [String] + -> Int + -> [[Block]] + -> State WriterState String +tableRowToDokuWiki opts alignStrings rownum cols' = do + let celltype = if rownum == 0 then "th" else "td" + let rowclass = case rownum of + 0 -> "header" + x | x `rem` 2 == 1 -> "odd" + _ -> "even" + cols'' <- sequence $ zipWith + (\alignment item -> tableItemToDokuWiki opts celltype alignment item) + alignStrings cols' + return $ "\n" ++ unlines cols'' ++ "" + +alignmentToString :: Alignment -> [Char] +alignmentToString alignment = case alignment of + AlignLeft -> "left" + AlignRight -> "right" + AlignCenter -> "center" + AlignDefault -> "left" + +tableItemToDokuWiki :: WriterOptions + -> String + -> String + -> [Block] + -> State WriterState String +tableItemToDokuWiki opts celltype align' item = do + let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++ + x ++ "" + contents <- blockListToDokuWiki opts item + return $ mkcell contents + +-- | Convert list of Pandoc block elements to DokuWiki. +blockListToDokuWiki :: WriterOptions -- ^ Options + -> [Block] -- ^ List of block elements + -> State WriterState String +blockListToDokuWiki opts blocks = + mapM (blockToDokuWiki opts) blocks >>= return . vcat + +-- | Convert list of Pandoc inline elements to DokuWiki. +inlineListToDokuWiki :: WriterOptions -> [Inline] -> State WriterState String +inlineListToDokuWiki opts lst = + mapM (inlineToDokuWiki opts) lst >>= return . concat + +-- | Convert Pandoc inline element to DokuWiki. +inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String + +inlineToDokuWiki opts (Emph lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "''" ++ contents ++ "''" + +inlineToDokuWiki opts (Strong lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "'''" ++ contents ++ "'''" + +inlineToDokuWiki opts (Strikeout lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "" ++ contents ++ "" + +inlineToDokuWiki opts (Superscript lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "" ++ contents ++ "" + +inlineToDokuWiki opts (Subscript lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "" ++ contents ++ "" + +inlineToDokuWiki opts (SmallCaps lst) = inlineListToDokuWiki opts lst + +inlineToDokuWiki opts (Quoted SingleQuote lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "\8216" ++ contents ++ "\8217" + +inlineToDokuWiki opts (Quoted DoubleQuote lst) = do + contents <- inlineListToDokuWiki opts lst + return $ "\8220" ++ contents ++ "\8221" + +inlineToDokuWiki opts (Cite _ lst) = inlineListToDokuWiki opts lst + +inlineToDokuWiki _ (Code _ str) = + return $ "" ++ (escapeString str) ++ "" + +inlineToDokuWiki _ (Str str) = return $ escapeString str + +inlineToDokuWiki _ (Math _ str) = return $ "" ++ str ++ "" + -- note: str should NOT be escaped + +inlineToDokuWiki _ (RawInline "mediawiki" str) = return str +inlineToDokuWiki _ (RawInline "html" str) = return str +inlineToDokuWiki _ (RawInline _ _) = return "" + +inlineToDokuWiki _ (LineBreak) = return "
    " + +inlineToDokuWiki _ Space = return " " + +inlineToDokuWiki opts (Link txt (src, _)) = do + label <- inlineListToDokuWiki opts txt + case txt of + [Str s] | escapeURI s == src -> return src + _ -> if isURI src + then return $ "[" ++ src ++ " " ++ label ++ "]" + else return $ "[[" ++ src' ++ "|" ++ label ++ "]]" + where src' = case src of + '/':xs -> xs -- with leading / it's a + _ -> src -- link to a help page +inlineToDokuWiki opts (Image alt (source, tit)) = do + alt' <- inlineListToDokuWiki opts alt + let txt = if (null tit) + then if null alt + then "" + else "|" ++ alt' + else "|" ++ tit + return $ "[[Image:" ++ source ++ txt ++ "]]" + +inlineToDokuWiki opts (Note contents) = do + contents' <- blockListToDokuWiki opts contents + modify (\s -> s { stNotes = True }) + return $ "" ++ contents' ++ "" + -- note - may not work for notes with multiple blocks -- cgit v1.2.3 From a43e5983da90419c5b6c01fe03febc3797c2d9aa Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Sun, 14 Jul 2013 14:24:20 +0100 Subject: Implemented correct output of dokuwiki (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 62 ++++++++++++++++++------------------- 2 files changed, 32 insertions(+), 32 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index b3483adf2..dabece5f0 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -112,7 +112,7 @@ blockToDokuWiki _ HorizontalRule = return "\n-----\n" blockToDokuWiki opts (Header level _ inlines) = do contents <- inlineListToDokuWiki opts inlines - let eqs = replicate level '=' + let eqs = replicate ( 7 - level ) '=' return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n" blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 7eccc44e8..013c629d8 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -3,32 +3,32 @@ This is a set of tests for pandoc. Most of them are adapted from John Gruber’s ----- -= Headers = +====== Headers ====== -== Level 2 with an [[url|embedded link]] == +===== Level 2 with an [[url|embedded link]] ===== -=== Level 3 with ''emphasis'' === +==== Level 3 with ''emphasis'' ==== -==== Level 4 ==== +=== Level 4 === -===== Level 5 ===== +== Level 5 == -= Level 1 = +====== Level 1 ====== -== Level 2 with ''emphasis'' == +===== 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. @@ -41,7 +41,7 @@ There should be a hard line break
    here. ----- -= Block Quotes = +====== Block Quotes ====== E-mail style: @@ -70,7 +70,7 @@ And a following paragraph. ----- -= Code Blocks = +====== Code Blocks ====== Code: @@ -89,9 +89,9 @@ These should not be escaped: \$ \\ \> \[ \{ ----- -= Lists = +====== Lists ====== -== Unordered == +===== Unordered ===== Asterisks tight: @@ -129,7 +129,7 @@ Minuses loose: * Minus 2 * Minus 3 -== Ordered == +===== Ordered ===== Tight: @@ -163,7 +163,7 @@ Multiple paragraphs:
  • Item 2.

  • Item 3.

  • -== Nested == +===== Nested ===== * Tab ** Tab @@ -187,14 +187,14 @@ Same thing but with paragraphs: #* Foe # 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 =====
    1. begins with 2
    2. @@ -238,7 +238,7 @@ B. Williams ----- -= Definition Lists = +====== Definition Lists ====== Tight using spaces: @@ -306,7 +306,7 @@ Blank line after term, indented marker, alternate markers: ;# sublist ;# sublist -= HTML Blocks = +====== HTML Blocks ====== Simple block on one line: @@ -416,7 +416,7 @@ Hr’s: ----- -= Inline Markup = +====== Inline Markup ====== This is ''emphasized'', and so ''is this''. @@ -445,7 +445,7 @@ These should not be superscripts or subscripts, because of the unescaped spaces: ----- -= Smart quotes, ellipses, dashes = +====== Smart quotes, ellipses, dashes ====== “Hello,” said the spider. “‘Shelob’ is my name.” @@ -466,7 +466,7 @@ Ellipses…and…and…. ----- -= LaTeX = +====== LaTeX ====== * * 2+2=4 @@ -490,7 +490,7 @@ Here’s a LaTeX table: ----- -= Special Characters = +====== Special Characters ====== Here is some unicode: @@ -545,9 +545,9 @@ Minus: - ----- -= Links = +====== Links ====== -== Explicit == +===== Explicit ===== Just a [[url/|URL]]. @@ -567,7 +567,7 @@ Just a [[url/|URL]]. [[|Empty]]. -== Reference == +===== Reference ===== Foo [[url/|bar]]. @@ -592,7 +592,7 @@ 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]. @@ -602,7 +602,7 @@ 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 @@ -620,7 +620,7 @@ Auto-links should not occur here: <http://example.com/> ----- -= Images = +====== Images ====== From “Voyage dans la Lune” by Georges Melies (1902): @@ -631,7 +631,7 @@ Here is a movie [[Image:movie.jpg|movie]] icon. ----- -= Footnotes = +====== Footnotes ====== Here is a footnote reference,Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. and another.Here’s the long note. This one contains multiple blocks. -- cgit v1.2.3 From 2afa4ec92418d87002f99c44c71fe743fa1f30d0 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Sun, 14 Jul 2013 14:58:42 +0100 Subject: Implemented Emphasis (italic) and Strong (bold) for dokuwiki (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- tests/writer.dokuwiki | 36 ++++++++++++++++++------------------ 2 files changed, 20 insertions(+), 20 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index dabece5f0..e9c0ecb02 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -335,11 +335,11 @@ inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String inlineToDokuWiki opts (Emph lst) = do contents <- inlineListToDokuWiki opts lst - return $ "''" ++ contents ++ "''" + return $ "//" ++ contents ++ "//" inlineToDokuWiki opts (Strong lst) = do contents <- inlineListToDokuWiki opts lst - return $ "'''" ++ contents ++ "'''" + return $ "**" ++ contents ++ "**" inlineToDokuWiki opts (Strikeout lst) = do contents <- inlineListToDokuWiki opts lst diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 013c629d8..32f984ef9 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -7,7 +7,7 @@ This is a set of tests for pandoc. Most of them are adapted from John Gruber’s ===== Level 2 with an [[url|embedded link]] ===== -==== Level 3 with ''emphasis'' ==== +==== Level 3 with //emphasis// ==== === Level 4 === @@ -15,7 +15,7 @@ This is a set of tests for pandoc. Most of them are adapted from John Gruber’s ====== Level 1 ====== -===== Level 2 with ''emphasis'' ===== +===== Level 2 with //emphasis// ===== ==== Level 3 ==== @@ -270,10 +270,10 @@ Loose: Multiple blocks with italics:
      -
      ''apple''
      +
      //apple//

      red fruit

      contains seeds, crisp, pleasant to taste

      -
      ''orange''
      +
      //orange//

      orange fruit

      { orange code block }

      orange block quote

      @@ -332,10 +332,10 @@ Interpreted markdown in a table:
      -This is ''emphasized'' +This is //emphasized// -And this is '''strong''' +And this is **strong**
      @@ -418,25 +418,25 @@ Hr’s: ====== Inline Markup ====== -This is ''emphasized'', and so ''is this''. +This is //emphasized//, and so //is this//. -This is '''strong''', and so '''is this'''. +This is **strong**, and so **is this**. -An ''[[url|emphasized link]]''. +An //[[url|emphasized link]]//. -'''''This is strong and em.''''' +**//This is strong and em.//** -So is '''''this''''' word. +So is **//this//** word. -'''''This is strong and em.''''' +**//This is strong and em.//** -So is '''''this''''' word. +So is **//this//** word. This is code: >, $, \, \$, <html>. -This is ''strikeout''. +This is //strikeout//. -Superscripts: abcd a''hello'' ahello there. +Superscripts: abcd a//hello// ahello there. Subscripts: H2O, H23O, Hmany of themO. @@ -480,9 +480,9 @@ Ellipses…and…and…. 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.) +* $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$. +* Escaped $: $73 //this should be emphasized// 23$. Here’s a LaTeX table: @@ -640,7 +640,7 @@ Subsequent blocks are indented to show that they belong to the footnote (as with
        { <code> }
      If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. -
      This should ''not'' be a footnote reference, because it contains a space.[^my note] Here is an inline note.This is ''easier'' to type. Inline notes may contain [http://google.com links] and ] verbatim characters, as well as [bracketed text]. + This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.This is //easier// to type. Inline notes may contain [http://google.com links] and ] verbatim characters, as well as [bracketed text].
      Notes can go in quotes.In quote. -- cgit v1.2.3 From 660fb244721a83985f097886178c5a38f6c8194e Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Sun, 14 Jul 2013 15:03:40 +0100 Subject: Implemented horizontal rule for dokuwiki (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 26 +++++++++++++------------- 2 files changed, 14 insertions(+), 14 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index e9c0ecb02..0169e0931 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -108,7 +108,7 @@ blockToDokuWiki _ (RawBlock "mediawiki" str) = return str blockToDokuWiki _ (RawBlock "html" str) = return str blockToDokuWiki _ (RawBlock _ _) = return "" -blockToDokuWiki _ HorizontalRule = return "\n-----\n" +blockToDokuWiki _ HorizontalRule = return "\n----\n" blockToDokuWiki opts (Header level _ inlines) = do contents <- inlineListToDokuWiki opts inlines diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 32f984ef9..0062de3b3 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -1,7 +1,7 @@ This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite. ------ +---- ====== Headers ====== @@ -26,7 +26,7 @@ with no blank line with no blank line ------ +---- ====== Paragraphs ====== @@ -39,7 +39,7 @@ Here’s one with a bullet. * criminey. There should be a hard line break
      here. ------ +---- ====== Block Quotes ====== @@ -68,7 +68,7 @@ This should not be a block quote: 2 > 1. And a following paragraph. ------ +---- ====== Code Blocks ====== @@ -87,7 +87,7 @@ And: These should not be escaped: \$ \\ \> \[ \{ ------ +---- ====== Lists ====== @@ -236,7 +236,7 @@ M.A. 2007 B. Williams ------ +---- ====== Definition Lists ====== @@ -414,7 +414,7 @@ Hr’s:
      ------ +---- ====== Inline Markup ====== @@ -443,7 +443,7 @@ Subscripts: H2O, H23O, Hmany of themO. These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d. ------ +---- ====== Smart quotes, ellipses, dashes ====== @@ -464,7 +464,7 @@ Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. ------ +---- ====== LaTeX ====== @@ -488,7 +488,7 @@ Here’s a LaTeX table: ------ +---- ====== Special Characters ====== @@ -543,7 +543,7 @@ Plus: + Minus: - ------ +---- ====== Links ====== @@ -618,7 +618,7 @@ Auto-links should not occur here: <http://example.com/>
      or here: <http://example.com/>
      ------ +---- ====== Images ====== @@ -629,7 +629,7 @@ From “Voyage dans la Lune” by Georges Melies (1902): Here is a movie [[Image:movie.jpg|movie]] icon. ------ +---- ====== Footnotes ====== -- cgit v1.2.3 From b2a8731e32c27a230a970b747df13ad84d473b5d Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Mon, 15 Jul 2013 09:35:04 +0100 Subject: Weak implementation of hyperlinks for dokuwiki (#386) TODO Simplify the code --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 0169e0931..b6929ad1e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -386,7 +386,7 @@ inlineToDokuWiki opts (Link txt (src, _)) = do case txt of [Str s] | escapeURI s == src -> return src _ -> if isURI src - then return $ "[" ++ src ++ " " ++ label ++ "]" + then return $ "[[" ++ src ++ "|" ++ label ++ "]]" else return $ "[[" ++ src' ++ "|" ++ label ++ "]]" where src' = case src of '/':xs -> xs -- with leading / it's a diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 0062de3b3..2a006f817 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -455,7 +455,7 @@ These should not be superscripts or subscripts, because of the unescaped spaces: ‘He said, “I want to go.”’ Were you alive in the 70’s? -Here is some quoted ‘code’ and a “[http://example.com/?foo=1&bar=2 quoted link]”. +Here is some quoted ‘code’ and a “[[http://example.com/?foo=1&bar=2|quoted link]]”. Some dashes: one—two — three—four — five. @@ -563,7 +563,7 @@ Just a [[url/|URL]]. [[url/with_underscore|with_underscore]] -[mailto:nobody@nowhere.net Email link] +[[mailto:nobody@nowhere.net|Email link]] [[|Empty]]. @@ -594,9 +594,9 @@ Foo [[url/|biz]]. ===== With ampersands ===== -Here’s a [http://example.com/?foo=1&bar=2 link with an ampersand in the URL]. +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 a link with an amersand in the link text: [[http://att.com/|AT&T]]. Here’s an [[script?foo=1&bar=2|inline link]]. @@ -610,7 +610,7 @@ With an ampersand: http://example.com/?foo=1&bar=2 * http://example.com/ * It should. -An e-mail address: [mailto:nobody@nowhere.net nobody@nowhere.net] +An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]]
      Blockquoted: http://example.com/
      @@ -640,7 +640,7 @@ Subsequent blocks are indented to show that they belong to the footnote (as with
        { <code> }
      If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. -
      This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.This is //easier// to type. Inline notes may contain [http://google.com links] and ] verbatim characters, as well as [bracketed text]. + This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ] verbatim characters, as well as [bracketed text].
      Notes can go in quotes.In quote. -- cgit v1.2.3 From 18565e149a2de3f6bb83563890cc9e4f65679693 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Mon, 15 Jul 2013 19:29:39 +0100 Subject: Implement conversion of images in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 9 +++++---- tests/writer.dokuwiki | 4 ++-- 2 files changed, 7 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index b6929ad1e..0651a8177 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -87,14 +87,15 @@ blockToDokuWiki opts (Plain inlines) = inlineListToDokuWiki opts inlines -- title beginning with fig: indicates that the image is a figure +-- dokuwiki doesn't support captions - so combine together alt and caption into alt blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do capt <- if null txt then return "" - else ("|caption " ++) `fmap` inlineListToDokuWiki opts txt + else (" " ++) `fmap` inlineListToDokuWiki opts txt let opt = if null txt then "" - else "|alt=" ++ if null tit then capt else tit ++ capt - return $ "[[Image:" ++ src ++ "|frame|none" ++ opt ++ "]]\n" + else "|" ++ if null tit then capt else tit ++ capt + return $ "{{:" ++ src ++ opt ++ "}}\n" blockToDokuWiki opts (Para inlines) = do useTags <- get >>= return . stUseTags @@ -398,7 +399,7 @@ inlineToDokuWiki opts (Image alt (source, tit)) = do then "" else "|" ++ alt' else "|" ++ tit - return $ "[[Image:" ++ source ++ txt ++ "]]" + return $ "{{:" ++ source ++ txt ++ "}}" inlineToDokuWiki opts (Note contents) = do contents' <- blockListToDokuWiki opts contents diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 2a006f817..b3f3b3dd2 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -624,9 +624,9 @@ Auto-links should not occur here: <http://example.com/> From “Voyage dans la Lune” by Georges Melies (1902): -[[Image:lalune.jpg|frame|none|alt=Voyage dans la Lune|caption lalune]] +{{:lalune.jpg|Voyage dans la Lune lalune}} -Here is a movie [[Image:movie.jpg|movie]] icon. +Here is a movie {{:movie.jpg|movie}} icon. ---- -- cgit v1.2.3 From 5b04d063a1637a24a3bb495718046c1f29525fea Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Fri, 26 Jul 2013 06:19:40 +0100 Subject: Convert bullet and numbered lists in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 31 ++++++++++++++++++++----- tests/writer.dokuwiki | 46 ++++++++++++++++++------------------- 2 files changed, 48 insertions(+), 29 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 0651a8177..4b72d0f14 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -167,7 +167,7 @@ blockToDokuWiki opts x@(BulletList items) = do modify $ \s -> s { stUseTags = oldUseTags } return $ "
        \n" ++ vcat contents ++ "
      \n" else do - modify $ \s -> s { stListLevel = stListLevel s ++ "*" } + modify $ \s -> s { stListLevel = stListLevel s ++ " " } contents <- mapM (listItemToDokuWiki opts) items modify $ \s -> s { stListLevel = init (stListLevel s) } return $ vcat contents ++ if null listLevel then "\n" else "" @@ -179,15 +179,18 @@ blockToDokuWiki opts x@(OrderedList attribs items) = do if useTags then do modify $ \s -> s { stUseTags = True } - contents <- mapM (listItemToDokuWiki opts) items + contents <- mapM (orderedListItemToDokuWiki opts) items modify $ \s -> s { stUseTags = oldUseTags } return $ "\n" ++ vcat contents ++ "
    \n" else do - modify $ \s -> s { stListLevel = stListLevel s ++ "#" } - contents <- mapM (listItemToDokuWiki opts) items + modify $ \s -> s { stListLevel = stListLevel s ++ " " } + contents <- mapM (orderedListItemToDokuWiki opts) items modify $ \s -> s { stListLevel = init (stListLevel s) } return $ vcat contents ++ if null listLevel then "\n" else "" +-- TODO Need to decide how to make definition lists work on dokuwiki - I don't think there +-- is a specific representation of them. +-- TODO This creates double '; ; ' if there is a bullet or ordered list inside a definition list blockToDokuWiki opts x@(DefinitionList items) = do oldUseTags <- get >>= return . stUseTags listLevel <- get >>= return . stListLevel @@ -217,7 +220,7 @@ listAttribsToString (startnum, numstyle, _) = then " style=\"list-style-type: " ++ numstyle' ++ ";\"" else "") --- | Convert bullet or ordered list item (list of blocks) to DokuWiki. +-- | Convert bullet list item (list of blocks) to DokuWiki. listItemToDokuWiki :: WriterOptions -> [Block] -> State WriterState String listItemToDokuWiki opts items = do contents <- blockListToDokuWiki opts items @@ -226,7 +229,23 @@ listItemToDokuWiki opts items = do then return $ "
  • " ++ contents ++ "
  • " else do marker <- get >>= return . stListLevel - return $ marker ++ " " ++ contents + -- This marker ++ marker is an awful hack to write 2 spaces per indentation level. + -- I couldn't find a cleaner way of doing it. + return $ marker ++ marker ++ "* " ++ contents + +-- | Convert ordered list item (list of blocks) to DokuWiki. +-- | TODO Emiminate dreadful duplication of text from listItemToDokuWiki +orderedListItemToDokuWiki :: WriterOptions -> [Block] -> State WriterState String +orderedListItemToDokuWiki opts items = do + contents <- blockListToDokuWiki opts items + useTags <- get >>= return . stUseTags + if useTags + then return $ "
  • " ++ contents ++ "
  • " + else do + marker <- get >>= return . stListLevel + -- This marker ++ marker is an awful hack to write 2 spaces per indentation level. + -- I couldn't find a cleaner way of doing it. + return $ marker ++ marker ++ "- " ++ contents -- | Convert definition list item (label, list of blocks) to DokuWiki. definitionListItemToDokuWiki :: WriterOptions diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 73afec027..7ffd254ef 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -303,8 +303,8 @@ Blank line after term, indented marker, alternate markers: : computer ; orange : orange fruit -;# sublist -;# sublist +; ; - sublist +; ; - sublist ====== HTML Blocks ====== @@ -468,21 +468,21 @@ Ellipses…and…and…. ====== LaTeX ====== -* -* 2+2=4 -* x \in y -* \alpha \wedge \omega -* 223 -* p-Tree -* Here’s some display math: \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. + * + * 2+2=4 + * x \in y + * \alpha \wedge \omega + * 223 + * p-Tree + * Here’s some display math: \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$. + * 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: @@ -494,11 +494,11 @@ Here’s a LaTeX table: Here is some unicode: -* I hat: Î -* o umlaut: ö -* section: § -* set membership: ∈ -* copyright: © + * I hat: Î + * o umlaut: ö + * section: § + * set membership: ∈ + * copyright: © AT&T has an ampersand in their name. @@ -606,9 +606,9 @@ Here’s an [[script?foo=1&bar=2|inline link in pointy braces]]. With an ampersand: http://example.com/?foo=1&bar=2 -* In a list? -* http://example.com/ -* It should. + * In a list? + * http://example.com/ + * It should. An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]] @@ -646,7 +646,7 @@ If you want, you can indent every line, but you can also be lazy and just indent
    Notes can go in quotes.In quote.
    -# And in list items.In list. + - And in list items.In list. This paragraph should not be part of the note, as it is not indented. -- cgit v1.2.3 From 2900a9a3718b0a2097d63cff76e7b9060c845837 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Fri, 26 Jul 2013 22:38:13 +0100 Subject: Added some todos to dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 4b72d0f14..d12ff2519 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -29,6 +29,21 @@ Conversion of 'Pandoc' documents to DokuWiki markup. DokuWiki: -} + +{- + [ ] Don't convert & to & + [ ] Don't generate
    ... + [ ] Don't generate
    ...
    +    [ ] Implement definition lists
    +    [ ] Don't generate lists using 
      and
        + [ ] Don't generate
        + [ ] Implement conversion of tables + [ ] Implement comments + [ ] Implement footnotes + [ ] Work through the Dokuwiki spec, and check I've not missed anything out + [ ] Test the output in Dokuwiki - and compare against the display of another format, e.g. HTML +-} + module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where import Text.Pandoc.Definition import Text.Pandoc.Options -- cgit v1.2.3 From b77d4456eaf871896ad7555607f968aa2ad9ad7c Mon Sep 17 00:00:00 2001 From: claremacrae Date: Fri, 26 Jul 2013 22:49:19 +0100 Subject: Added another todo - dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index d12ff2519..3344b146f 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -42,6 +42,7 @@ DokuWiki: [ ] Implement footnotes [ ] Work through the Dokuwiki spec, and check I've not missed anything out [ ] Test the output in Dokuwiki - and compare against the display of another format, e.g. HTML + [ ] Remove dud/duplicate code -} module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where -- cgit v1.2.3 From 51b8ce49f1c98f22987463cf891c8f20e4a9da54 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 28 Jul 2013 18:42:53 +0100 Subject: Implemented linebreaks in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 3344b146f..6946f7722 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -413,7 +413,7 @@ inlineToDokuWiki _ (RawInline "mediawiki" str) = return str inlineToDokuWiki _ (RawInline "html" str) = return str inlineToDokuWiki _ (RawInline _ _) = return "" -inlineToDokuWiki _ (LineBreak) = return "
        " +inlineToDokuWiki _ (LineBreak) = return "\\\\\n" inlineToDokuWiki _ Space = return " " diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 7ffd254ef..0d03ea8b3 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -36,7 +36,8 @@ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Beca Here’s one with a bullet. * criminey. -There should be a hard line break
        here. +There should be a hard line break\\ +here. ---- -- cgit v1.2.3 From b5f86a665d272a76d768ccdc6d7c19b13e884d29 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 28 Jul 2013 18:59:16 +0100 Subject: Removed incorrect entity conversion in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 7 +++---- tests/writer.dokuwiki | 16 ++++++++-------- 2 files changed, 11 insertions(+), 12 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 6946f7722..c4a99edca 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -31,7 +31,6 @@ DokuWiki: -} {- - [ ] Don't convert & to & [ ] Don't generate
        ... [ ] Don't generate
        ...
             [ ] Implement definition lists
        @@ -51,7 +50,7 @@ import Text.Pandoc.Options
         import Text.Pandoc.Shared
         import Text.Pandoc.Writers.Shared
         import Text.Pandoc.Templates (renderTemplate')
        -import Text.Pandoc.XML ( escapeStringForXML )
        +import Text.Pandoc.XML ( escapeStringForXML ) -- TODO Remove this line
         import Data.List ( intersect, intercalate )
         import Network.URI ( isURI )
         import Control.Monad.State
        @@ -89,7 +88,7 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do
              else return main
         
         -- | Escape special characters for DokuWiki.
        -escapeString :: String -> String
        +escapeString :: String -> String -- TODO Remove this
         escapeString =  escapeStringForXML
         
         -- | Convert Pandoc block element to DokuWiki.
        @@ -404,7 +403,7 @@ inlineToDokuWiki opts (Cite _  lst) = inlineListToDokuWiki opts lst
         inlineToDokuWiki _ (Code _ str) =
           return $ "" ++ (escapeString str) ++ ""
         
        -inlineToDokuWiki _ (Str str) = return $ escapeString str
        +inlineToDokuWiki _ (Str str) = return $ str
         
         inlineToDokuWiki _ (Math _ str) = return $ "" ++ str ++ ""
                                          -- note:  str should NOT be escaped
        diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki
        index 0d03ea8b3..742c9ca25 100644
        --- a/tests/writer.dokuwiki
        +++ b/tests/writer.dokuwiki
        @@ -64,7 +64,7 @@ Nested block quotes:
         
        nested
    -This should not be a block quote: 2 > 1. +This should not be a block quote: 2 > 1. And a following paragraph. @@ -501,15 +501,15 @@ Here is some unicode: * set membership: ∈ * copyright: © -AT&T has an ampersand in their name. +AT&T has an ampersand in their name. -AT&T is another way to write it. +AT&T is another way to write it. -This & that. +This & that. -4 < 5. +4 < 5. -6 > 5. +6 > 5. Backslash: \ @@ -531,7 +531,7 @@ Left paren: ( Right paren: ) -Greater-than: > +Greater-than: > Hash: # @@ -597,7 +597,7 @@ Foo [[url/|biz]]. 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 a link with an amersand in the link text: [[http://att.com/|AT&T]]. Here’s an [[script?foo=1&bar=2|inline link]]. -- cgit v1.2.3 From b14b2d6a85267cee3649048bb761a48cc0ab30be Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 28 Jul 2013 19:19:33 +0100 Subject: Implement footnotes in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 6 +++--- tests/writer.dokuwiki | 16 +++++++--------- 2 files changed, 10 insertions(+), 12 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index c4a99edca..b172741de 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -38,7 +38,6 @@ DokuWiki: [ ] Don't generate
    [ ] Implement conversion of tables [ ] Implement comments - [ ] Implement footnotes [ ] Work through the Dokuwiki spec, and check I've not missed anything out [ ] Test the output in Dokuwiki - and compare against the display of another format, e.g. HTML [ ] Remove dud/duplicate code @@ -77,7 +76,8 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do body <- blockListToDokuWiki opts blocks notesExist <- get >>= return . stNotes let notes = if notesExist - then "\n" + then "" -- TODO Was "\n" Check whether I can really remove this: + -- if it is definitely to do with footnotes, can remove this whole bit else "" let main = body ++ notes let context = defField "body" main @@ -438,5 +438,5 @@ inlineToDokuWiki opts (Image alt (source, tit)) = do inlineToDokuWiki opts (Note contents) = do contents' <- blockListToDokuWiki opts contents modify (\s -> s { stNotes = True }) - return $ "" ++ contents' ++ "" + return $ "((" ++ contents' ++ "))" -- note - may not work for notes with multiple blocks diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 742c9ca25..27fb29007 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -634,21 +634,19 @@ Here is a movie {{:movie.jpg|movie}} icon. ====== Footnotes ====== -Here is a footnote reference,Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. - and another.Here’s the long note. This one contains multiple blocks. +Here is a footnote reference,((Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. +)) and another.((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).
      { <code> }
    If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. -
    This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ] verbatim characters, as well as [bracketed text]. - +)) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ] verbatim characters, as well as [bracketed text]. +)) -
    Notes can go in quotes.In quote. - +
    Notes can go in quotes.((In quote. +))
    - - And in list items.In list. + - And in list items.((In list.)) This paragraph should not be part of the note, as it is not indented. - - -- cgit v1.2.3 From e5004bcff040a2bc85d7ed6acb42425d265f1bd2 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Tue, 6 Aug 2013 07:43:32 +0100 Subject: Implement strikeout in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index b172741de..db02bde89 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -378,7 +378,7 @@ inlineToDokuWiki opts (Strong lst) = do inlineToDokuWiki opts (Strikeout lst) = do contents <- inlineListToDokuWiki opts lst - return $ "" ++ contents ++ "" + return $ "" ++ contents ++ "" inlineToDokuWiki opts (Superscript lst) = do contents <- inlineListToDokuWiki opts lst diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 27fb29007..9063ab917 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -435,7 +435,7 @@ So is **//this//** word. This is code: >, $, \, \$, <html>. -This is //strikeout//. +This is //strikeout//. Superscripts: abcd a//hello// ahello there. -- cgit v1.2.3 From 48645a47555dd5c243f5d28f9c8274b368917856 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 11 Aug 2013 22:22:07 +0100 Subject: Initial implementation of tables in dokuwiki writer (#386) Todo: alignment, and headings --- src/Text/Pandoc/Writers/DokuWiki.hs | 39 +++---- tests/tables.dokuwiki | 217 +++++------------------------------- 2 files changed, 43 insertions(+), 213 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index db02bde89..87145d723 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -150,26 +150,21 @@ blockToDokuWiki opts (BlockQuote blocks) = do contents <- blockListToDokuWiki opts blocks return $ "
    " ++ contents ++ "
    " -blockToDokuWiki opts (Table capt aligns widths headers rows') = do +blockToDokuWiki opts (Table capt aligns _ headers rows') = do let alignStrings = map alignmentToString aligns captionDoc <- if null capt then return "" else do c <- inlineListToDokuWiki opts capt - return $ "" ++ c ++ "\n" - let percent w = show (truncate (100*w) :: Integer) ++ "%" - let coltags = if all (== 0.0) widths - then "" - else unlines $ map - (\w -> "") widths + return $ "" ++ c ++ "\n" head' <- if all null headers then return "" else do hs <- tableRowToDokuWiki opts alignStrings 0 headers - return $ "\n" ++ hs ++ "\n\n" + return $ hs ++ "\n" body' <- zipWithM (tableRowToDokuWiki opts alignStrings) [1..] rows' - return $ "\n" ++ captionDoc ++ coltags ++ head' ++ - "\n" ++ unlines body' ++ "\n
    \n" + return $ captionDoc ++ head' ++ + unlines body' blockToDokuWiki opts x@(BulletList items) = do oldUseTags <- get >>= return . stUseTags @@ -325,34 +320,34 @@ tableRowToDokuWiki :: WriterOptions -> [[Block]] -> State WriterState String tableRowToDokuWiki opts alignStrings rownum cols' = do - let celltype = if rownum == 0 then "th" else "td" - let rowclass = case rownum of - 0 -> "header" - x | x `rem` 2 == 1 -> "odd" - _ -> "even" + let celltype = if rownum == 0 then "" else "" cols'' <- sequence $ zipWith (\alignment item -> tableItemToDokuWiki opts celltype alignment item) alignStrings cols' - return $ "\n" ++ unlines cols'' ++ "" + return $ "| " ++ "" ++ joinColumns cols'' ++ " |" alignmentToString :: Alignment -> [Char] alignmentToString alignment = case alignment of - AlignLeft -> "left" - AlignRight -> "right" - AlignCenter -> "center" - AlignDefault -> "left" + AlignLeft -> "" + AlignRight -> "" + AlignCenter -> "" + AlignDefault -> "" tableItemToDokuWiki :: WriterOptions -> String -> String -> [Block] -> State WriterState String +-- TODO Fix celltype and align' defined but not used tableItemToDokuWiki opts celltype align' item = do - let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++ - x ++ "" + let mkcell x = "" ++ x ++ "" contents <- blockListToDokuWiki opts item return $ mkcell contents +-- | Concatenates columns together. +joinColumns :: [String] -> String +joinColumns = intercalate " | " + -- | Convert list of Pandoc block elements to DokuWiki. blockListToDokuWiki :: WriterOptions -- ^ Options -> [Block] -- ^ List of block elements diff --git a/tests/tables.dokuwiki b/tests/tables.dokuwiki index 4836ecd79..0a1b0a4ff 100644 --- a/tests/tables.dokuwiki +++ b/tests/tables.dokuwiki @@ -1,212 +1,47 @@ Simple table with caption: - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    Demonstration of simple table syntax.
    RightLeftCenterDefault
    12121212
    123123123123
    1111
    +Demonstration of simple table syntax. +| Right | Left | Center | Default | +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | Simple table without caption: - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    RightLeftCenterDefault
    12121212
    123123123123
    1111
    +| Right | Left | Center | Default | +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | Simple table indented two spaces: - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    Demonstration of simple table syntax.
    RightLeftCenterDefault
    12121212
    123123123123
    1111
    +Demonstration of simple table syntax. +| Right | Left | Center | Default | +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | Multiline table with caption: - - ----- - - - - - - - - - - - - - - - - - - - - - -
    Here's the caption. It may span multiple lines.
    Centered HeaderLeft AlignedRight AlignedDefault aligned
    Firstrow12.0Example of a row that spans multiple lines.
    Secondrow5.0Here's another one. Note the blank line between rows.
    +Here's the caption. It may span multiple lines. +| 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. | Multiline table without caption: - ----- - - - - - - - - - - - - - - - - - - - - - -
    Centered HeaderLeft AlignedRight AlignedDefault aligned
    Firstrow12.0Example of a row that spans multiple lines.
    Secondrow5.0Here's another one. Note the blank line between rows.
    +| 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: - - - - - - - - - - - - - - - - - - - - - -
    12121212
    123123123123
    1111
    +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | Multiline table without column headers: - ----- - - - - - - - - - - - - - -
    Firstrow12.0Example of a row that spans multiple lines.
    Secondrow5.0Here's another one. Note the blank line between rows.
    +| 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. | -- cgit v1.2.3 From eb4fe5e82c65b5dc2f5689e4b1bceff0179397b5 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sat, 17 Aug 2013 08:48:29 +0100 Subject: Implement table headings in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 21 +++++++++++++++++++-- tests/tables.dokuwiki | 10 +++++----- 2 files changed, 24 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 87145d723..76fe2fa36 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -36,7 +36,7 @@ DokuWiki: [ ] Implement definition lists [ ] Don't generate lists using
      and
        [ ] Don't generate
        - [ ] Implement conversion of tables + [ ] Implement alignment of text in tables [ ] Implement comments [ ] Work through the Dokuwiki spec, and check I've not missed anything out [ ] Test the output in Dokuwiki - and compare against the display of another format, e.g. HTML @@ -160,7 +160,7 @@ blockToDokuWiki opts (Table capt aligns _ headers rows') = do head' <- if all null headers then return "" else do - hs <- tableRowToDokuWiki opts alignStrings 0 headers + hs <- tableHeaderToDokuWiki opts alignStrings 0 headers return $ hs ++ "\n" body' <- zipWithM (tableRowToDokuWiki opts alignStrings) [1..] rows' return $ captionDoc ++ head' ++ @@ -314,6 +314,19 @@ vcat = intercalate "\n" -- Auxiliary functions for tables: +-- TODO Eliminate copy-and-pasted code in tableHeaderToDokuWiki and tableRowToDokuWiki +tableHeaderToDokuWiki :: WriterOptions + -> [String] + -> Int + -> [[Block]] + -> State WriterState String +tableHeaderToDokuWiki opts alignStrings rownum cols' = do + let celltype = if rownum == 0 then "" else "" + cols'' <- sequence $ zipWith + (\alignment item -> tableItemToDokuWiki opts celltype alignment item) + alignStrings cols' + return $ "^ " ++ "" ++ joinHeaders cols'' ++ " ^" + tableRowToDokuWiki :: WriterOptions -> [String] -> Int @@ -348,6 +361,10 @@ tableItemToDokuWiki opts celltype align' item = do joinColumns :: [String] -> String joinColumns = intercalate " | " +-- | Concatenates headers together. +joinHeaders :: [String] -> String +joinHeaders = intercalate " ^ " + -- | Convert list of Pandoc block elements to DokuWiki. blockListToDokuWiki :: WriterOptions -- ^ Options -> [Block] -- ^ List of block elements diff --git a/tests/tables.dokuwiki b/tests/tables.dokuwiki index 0a1b0a4ff..4fcae4e6f 100644 --- a/tests/tables.dokuwiki +++ b/tests/tables.dokuwiki @@ -1,14 +1,14 @@ Simple table with caption: Demonstration of simple table syntax. -| Right | Left | Center | Default | +^ Right ^ Left ^ Center ^ Default ^ | 12 | 12 | 12 | 12 | | 123 | 123 | 123 | 123 | | 1 | 1 | 1 | 1 | Simple table without caption: -| Right | Left | Center | Default | +^ Right ^ Left ^ Center ^ Default ^ | 12 | 12 | 12 | 12 | | 123 | 123 | 123 | 123 | | 1 | 1 | 1 | 1 | @@ -16,7 +16,7 @@ Simple table without caption: Simple table indented two spaces: Demonstration of simple table syntax. -| Right | Left | Center | Default | +^ Right ^ Left ^ Center ^ Default ^ | 12 | 12 | 12 | 12 | | 123 | 123 | 123 | 123 | | 1 | 1 | 1 | 1 | @@ -24,13 +24,13 @@ Demonstration of simple table syntax. Multiline table with caption: Here's the caption. It may span multiple lines. -| Centered Header | Left Aligned | Right Aligned | Default aligned | +^ 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. | Multiline table without caption: -| Centered Header | Left Aligned | Right Aligned | Default aligned | +^ 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. | -- cgit v1.2.3 From 573bd1b61b58e66c1e0ecfb4e74928a9d9d27daf Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sat, 17 Aug 2013 11:20:51 +0100 Subject: Implement blocks in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 3 +-- tests/writer.dokuwiki | 30 +++++++++++++++--------------- 2 files changed, 16 insertions(+), 17 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 76fe2fa36..97b1705d1 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -32,7 +32,6 @@ DokuWiki: {- [ ] Don't generate
        ... - [ ] Don't generate
        ...
             [ ] Implement definition lists
             [ ] Don't generate lists using 
          and
            [ ] Don't generate
            @@ -142,7 +141,7 @@ blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do "smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl", "visualfoxpro", "winbatch", "xml", "xpp", "z80"] let (beg, end) = if null at - then ("" else " class=\"" ++ unwords classes ++ "\">", "
        ") + then ("" else " class=\"" ++ unwords classes ++ "\">", "
        ") else ("", "") return $ beg ++ escapeString str ++ end diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 9063ab917..b9a8a3c05 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -50,9 +50,9 @@ E-mail style:
        Code in a block quote: -
        sub status {
        +sub status {
             print "working";
        -}
        +} A list: - item one @@ -75,18 +75,18 @@ And a following paragraph. Code: -
        ---- (should be four hyphens)
        +---- (should be four hyphens)
         
         sub status {
             print "working";
         }
         
        -this code block is indented by one tab
        +this code block is indented by one tab And: -
            this code block is indented by two tabs
        +    this code block is indented by two tabs
         
        -These should not be escaped:  \$ \\ \> \[ \{
        +These should not be escaped: \$ \\ \> \[ \{ ---- @@ -276,7 +276,7 @@ Multiple blocks with italics:

        contains seeds, crisp, pleasant to taste

        //orange//

        orange fruit

        -
        { orange code block }
        +{ orange code block }

        orange block quote

        Multiple definitions, tight: @@ -352,12 +352,12 @@ foo This should be a code block, though: -
        <div>
        +<div>
             foo
        -</div>
        +</div> As should this: -
        <div>foo</div>
        +<div>foo</div> Now, nested:
        @@ -386,14 +386,14 @@ Blah Code block: -
        <!-- Comment -->
        +<!-- Comment --> Just plain comment, with trailing spaces on the line: Code: -
        <hr />
        +<hr /> Hr’s:
        @@ -588,7 +588,7 @@ Indented [[url|thrice]]. This should [not][] be a link. -
        [not]: /url
        +[not]: /url Foo [[url/|bar]]. Foo [[url/|biz]]. @@ -617,7 +617,7 @@ An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]]
        Auto-links should not occur here: <http://example.com/> -
        or here: <http://example.com/>
        +or here: <http://example.com/> ---- @@ -639,7 +639,7 @@ Here is a footnote reference,((Here is the footnote. It can go anywhere after th Subsequent blocks are indented to show that they belong to the footnote (as with list items). -
          { <code> }
        + { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. )) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ] verbatim characters, as well as [bracketed text]. )) -- cgit v1.2.3 From 4c48433a2aaae080acbd74450bd5f70b714475be Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sat, 17 Aug 2013 12:20:34 +0100 Subject: Don't add entities in blocks in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 20 ++++++++++---------- 2 files changed, 11 insertions(+), 11 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 97b1705d1..b9eb444b3 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -143,7 +143,7 @@ blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do let (beg, end) = if null at then ("" else " class=\"" ++ unwords classes ++ "\">", "") else ("", "") - return $ beg ++ escapeString str ++ end + return $ beg ++ str ++ end blockToDokuWiki opts (BlockQuote blocks) = do contents <- blockListToDokuWiki opts blocks diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index b9a8a3c05..489726a76 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -51,7 +51,7 @@ E-mail style:
        Code in a block quote: sub status { - print "working"; + print "working"; } A list: @@ -78,7 +78,7 @@ Code: ---- (should be four hyphens) sub status { - print "working"; + print "working"; } this code block is indented by one tab @@ -86,7 +86,7 @@ And: this code block is indented by two tabs -These should not be escaped: \$ \\ \> \[ \{ +These should not be escaped: \$ \\ \> \[ \{ ---- @@ -352,12 +352,12 @@ foo This should be a code block, though: -<div> +
        foo -</div> +
        As should this: -<div>foo</div> +
        foo
        Now, nested:
        @@ -386,14 +386,14 @@ Blah Code block: -<!-- Comment --> + Just plain comment, with trailing spaces on the line: Code: -<hr /> +
        Hr’s:
        @@ -617,7 +617,7 @@ An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]]
        Auto-links should not occur here: <http://example.com/> -or here: <http://example.com/> +or here: ---- @@ -639,7 +639,7 @@ Here is a footnote reference,((Here is the footnote. It can go anywhere after th Subsequent blocks are indented to show that they belong to the footnote (as with list items). - { <code> } + { } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. )) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ] verbatim characters, as well as [bracketed text]. )) -- cgit v1.2.3 From 0961d499121e20473dfc02cfd1d7282f89436700 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sat, 17 Aug 2013 12:34:05 +0100 Subject: Fixed inlined code in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 7 +------ tests/writer.dokuwiki | 12 ++++++------ 2 files changed, 7 insertions(+), 12 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index b9eb444b3..3f4efb1b3 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -48,7 +48,6 @@ import Text.Pandoc.Options import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Templates (renderTemplate') -import Text.Pandoc.XML ( escapeStringForXML ) -- TODO Remove this line import Data.List ( intersect, intercalate ) import Network.URI ( isURI ) import Control.Monad.State @@ -86,10 +85,6 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do then return $ renderTemplate' (writerTemplate opts) context else return main --- | Escape special characters for DokuWiki. -escapeString :: String -> String -- TODO Remove this -escapeString = escapeStringForXML - -- | Convert Pandoc block element to DokuWiki. blockToDokuWiki :: WriterOptions -- ^ Options -> Block -- ^ Block element @@ -412,7 +407,7 @@ inlineToDokuWiki opts (Quoted DoubleQuote lst) = do inlineToDokuWiki opts (Cite _ lst) = inlineListToDokuWiki opts lst inlineToDokuWiki _ (Code _ str) = - return $ "" ++ (escapeString str) ++ "" + return $ "''" ++ str++ "''" inlineToDokuWiki _ (Str str) = return $ str diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 489726a76..8aeb52bd6 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -433,7 +433,7 @@ So is **//this//** word. So is **//this//** word. -This is code: >, $, \, \$, <html>. +This is code: ''>'', ''$'', ''\'', ''\$'', ''''. This is //strikeout//. @@ -456,7 +456,7 @@ These should not be superscripts or subscripts, because of the unescaped spaces: ‘He said, “I want to go.”’ Were you alive in the 70’s? -Here is some quoted ‘code’ and a “[[http://example.com/?foo=1&bar=2|quoted link]]”. +Here is some quoted ‘''code''’ and a “[[http://example.com/?foo=1&bar=2|quoted link]]”. Some dashes: one—two — three—four — five. @@ -480,10 +480,10 @@ Ellipses…and…and…. These shouldn’t be math: - * To get the famous equation, write $e = mc^2$. + * 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$. + * Escaped ''$'': $73 //this should be emphasized// 23$. Here’s a LaTeX table: @@ -615,7 +615,7 @@ An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]]
        Blockquoted: http://example.com/
        -Auto-links should not occur here: <http://example.com/> +Auto-links should not occur here: '''' or here: @@ -641,7 +641,7 @@ Subsequent blocks are indented to show that they belong to the footnote (as with { } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. -)) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ] verbatim characters, as well as [bracketed text]. +)) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and '']'' verbatim characters, as well as [bracketed text]. ))
        Notes can go in quotes.((In quote. -- cgit v1.2.3 From 2a4bbe5d4f433648be8b8ddb6079e5e09153d722 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sat, 17 Aug 2013 22:28:07 +0100 Subject: Nasty hack to stop C comments in inline code becoming italics in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 7 ++++++- tests/dokuwiki-writer.dokuwiki | 2 +- 2 files changed, 7 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 3f4efb1b3..9ac35ebd6 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -85,6 +85,11 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do then return $ renderTemplate' (writerTemplate opts) context else return main +-- | Escape special characters for MediaWiki. +escapeString :: String -> String +-- The spaces around // are to prevent touching in URLs inside inline code blocks +escapeString str = substitute " // " " %%//%% " str + -- | Convert Pandoc block element to DokuWiki. blockToDokuWiki :: WriterOptions -- ^ Options -> Block -- ^ Block element @@ -407,7 +412,7 @@ inlineToDokuWiki opts (Quoted DoubleQuote lst) = do inlineToDokuWiki opts (Cite _ lst) = inlineListToDokuWiki opts lst inlineToDokuWiki _ (Code _ str) = - return $ "''" ++ str++ "''" + return $ "''" ++ ( escapeString str ) ++ "''" inlineToDokuWiki _ (Str str) = return $ str diff --git a/tests/dokuwiki-writer.dokuwiki b/tests/dokuwiki-writer.dokuwiki index d6ab65d66..dbffb7a0e 100644 --- a/tests/dokuwiki-writer.dokuwiki +++ b/tests/dokuwiki-writer.dokuwiki @@ -1,3 +1,3 @@ hello // world ** from __ me -''hello // world ** from __ me'' +''hello %%//%% world ** from __ me'' -- cgit v1.2.3 From 6d484bc55e2bc8d318b0727bcd88e4ceea795329 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 18 Aug 2013 08:13:34 +0100 Subject: Treat inline code blocks like instead of in dokuwiki writer (#386) Done because I noticed that in the Autolinks section of writer.dokuwiki, the URL in inlined code was getting auto-linked, when it wasn't supposed to. This also meant that any inline code examples that had text that looked like dokuwiki syntax could break the formatting of later text. --- src/Text/Pandoc/Writers/DokuWiki.hs | 11 ++++++++++- tests/dokuwiki-writer.dokuwiki | 2 +- tests/writer.dokuwiki | 12 ++++++------ 3 files changed, 17 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 9ac35ebd6..a38a54953 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -412,7 +412,16 @@ inlineToDokuWiki opts (Quoted DoubleQuote lst) = do inlineToDokuWiki opts (Cite _ lst) = inlineListToDokuWiki opts lst inlineToDokuWiki _ (Code _ str) = - return $ "''" ++ ( escapeString str ) ++ "''" + -- In dokuwiki, text surrounded by '' is really just a font statement, i.e. , + -- and so other formatting can be present inside. + -- However, in pandoc, and markdown, inlined code doesn't contain formatting. + -- So I have opted for using %% to disable all formatting inside inline code blocks. + -- This gives the best results when converting from other formats to dokuwiki, even if + -- the resultand code is a little ugly, for short strings that don't contain formatting + -- characters. + -- It does mean that if pandoc could ever read dokuwiki, and so round-trip the format, + -- any formatting inside inlined code blocks would be lost, or presented incorrectly. + return $ "''%%" ++ str ++ "%%''" inlineToDokuWiki _ (Str str) = return $ str diff --git a/tests/dokuwiki-writer.dokuwiki b/tests/dokuwiki-writer.dokuwiki index dbffb7a0e..44f06f777 100644 --- a/tests/dokuwiki-writer.dokuwiki +++ b/tests/dokuwiki-writer.dokuwiki @@ -1,3 +1,3 @@ hello // world ** from __ me -''hello %%//%% world ** from __ me'' +''%%hello // world ** from __ me%%'' diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 8aeb52bd6..9855f30dd 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -433,7 +433,7 @@ So is **//this//** word. So is **//this//** word. -This is code: ''>'', ''$'', ''\'', ''\$'', ''''. +This is code: ''%%>%%'', ''%%$%%'', ''%%\%%'', ''%%\$%%'', ''%%%%''. This is //strikeout//. @@ -456,7 +456,7 @@ These should not be superscripts or subscripts, because of the unescaped spaces: ‘He said, “I want to go.”’ Were you alive in the 70’s? -Here is some quoted ‘''code''’ and a “[[http://example.com/?foo=1&bar=2|quoted link]]”. +Here is some quoted ‘''%%code%%''’ and a “[[http://example.com/?foo=1&bar=2|quoted link]]”. Some dashes: one—two — three—four — five. @@ -480,10 +480,10 @@ Ellipses…and…and…. These shouldn’t be math: - * To get the famous equation, write ''$e = mc^2$''. + * 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$. + * Escaped ''%%$%%'': $73 //this should be emphasized// 23$. Here’s a LaTeX table: @@ -615,7 +615,7 @@ An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]]
        Blockquoted: http://example.com/
        -Auto-links should not occur here: '''' +Auto-links should not occur here: ''%%%%'' or here: @@ -641,7 +641,7 @@ Subsequent blocks are indented to show that they belong to the footnote (as with { } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. -)) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and '']'' verbatim characters, as well as [bracketed text]. +)) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ''%%]%%'' verbatim characters, as well as [bracketed text]. ))
        Notes can go in quotes.((In quote. -- cgit v1.2.3 From b5b622f5b821ed5624b0ce2f29d1bddd0100bd04 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 18 Aug 2013 08:57:32 +0100 Subject: Stop plain text // becoming an italic marker in dokuwiki writer (#386) When the original document had text containing //, this was previously included, unchanged, in the dokuwiki output, and this interacted badly with later, intended, formating text. --- src/Text/Pandoc/Writers/DokuWiki.hs | 5 ++--- tests/dokuwiki-writer.dokuwiki | 2 +- 2 files changed, 3 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index a38a54953..4e7e79441 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -87,8 +87,7 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do -- | Escape special characters for MediaWiki. escapeString :: String -> String --- The spaces around // are to prevent touching in URLs inside inline code blocks -escapeString str = substitute " // " " %%//%% " str +escapeString str = substitute "//" "%%//%%" str -- | Convert Pandoc block element to DokuWiki. blockToDokuWiki :: WriterOptions -- ^ Options @@ -423,7 +422,7 @@ inlineToDokuWiki _ (Code _ str) = -- any formatting inside inlined code blocks would be lost, or presented incorrectly. return $ "''%%" ++ str ++ "%%''" -inlineToDokuWiki _ (Str str) = return $ str +inlineToDokuWiki _ (Str str) = return $ escapeString str inlineToDokuWiki _ (Math _ str) = return $ "" ++ str ++ "" -- note: str should NOT be escaped diff --git a/tests/dokuwiki-writer.dokuwiki b/tests/dokuwiki-writer.dokuwiki index 44f06f777..2e5d2fc1c 100644 --- a/tests/dokuwiki-writer.dokuwiki +++ b/tests/dokuwiki-writer.dokuwiki @@ -1,3 +1,3 @@ -hello // world ** from __ me +hello %%//%% world ** from __ me ''%%hello // world ** from __ me%%'' -- cgit v1.2.3 From 288329044a63331658079aa9db57b46fe204b6b9 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Sun, 18 Aug 2013 09:15:33 +0100 Subject: Stop plain text ** and __ becoming formatting in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/dokuwiki-writer.dokuwiki | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 4e7e79441..ec22a5a82 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -87,7 +87,7 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do -- | Escape special characters for MediaWiki. escapeString :: String -> String -escapeString str = substitute "//" "%%//%%" str +escapeString str = substitute "__" "%%__%%" ( substitute "**" "%%**%%" ( substitute "//" "%%//%%" str ) ) -- | Convert Pandoc block element to DokuWiki. blockToDokuWiki :: WriterOptions -- ^ Options diff --git a/tests/dokuwiki-writer.dokuwiki b/tests/dokuwiki-writer.dokuwiki index 2e5d2fc1c..6ddacc480 100644 --- a/tests/dokuwiki-writer.dokuwiki +++ b/tests/dokuwiki-writer.dokuwiki @@ -1,3 +1,3 @@ -hello %%//%% world ** from __ me +hello %%//%% world %%**%% from %%__%% me ''%%hello // world ** from __ me%%'' -- cgit v1.2.3 From 883f119c871a9fce402ceace8492a3cef06c5e81 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Mon, 19 Aug 2013 08:09:52 +0100 Subject: Removed unnecessary line-break after hard break in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 3 +-- 2 files changed, 2 insertions(+), 3 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index ec22a5a82..523c4d180 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -431,7 +431,7 @@ inlineToDokuWiki _ (RawInline "mediawiki" str) = return str inlineToDokuWiki _ (RawInline "html" str) = return str inlineToDokuWiki _ (RawInline _ _) = return "" -inlineToDokuWiki _ (LineBreak) = return "\\\\\n" +inlineToDokuWiki _ (LineBreak) = return "\\\\ " inlineToDokuWiki _ Space = return " " diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 9855f30dd..4b9d459c8 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -36,8 +36,7 @@ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Beca Here’s one with a bullet. * criminey. -There should be a hard line break\\ -here. +There should be a hard line break\\ here. ---- -- cgit v1.2.3 From 6cc284cc8eadf6a1d9099b7f1e2b68b3d1ac4561 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Mon, 19 Aug 2013 20:45:31 +0100 Subject: Bullet and ordered lists now always simple in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 5 ++--- tests/writer.dokuwiki | 43 +++++++++++++------------------------ 2 files changed, 17 insertions(+), 31 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 523c4d180..0f62e98c3 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -275,9 +275,8 @@ definitionListItemToDokuWiki opts (label, items) = do isSimpleList :: Block -> Bool isSimpleList x = case x of - BulletList items -> all isSimpleListItem items - OrderedList (num, sty, _) items -> all isSimpleListItem items && - num == 1 && sty `elem` [DefaultStyle, Decimal] + BulletList items -> True + OrderedList (num, sty, _) items -> True DefinitionList items -> all isSimpleListItem $ concatMap snd items _ -> False diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 4b9d459c8..e881f3510 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -157,11 +157,10 @@ and using spaces: Multiple paragraphs: -
          -
        1. Item 1, graf one.

          -

          Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.

        2. -
        3. Item 2.

        4. -
        5. Item 3.

        + - Item 1, graf one. +Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. + - Item 2. + - Item 3. ===== Nested ===== @@ -196,32 +195,20 @@ Same thing but with paragraphs: ===== Fancy list markers ===== -
          -
        1. begins with 2
        2. -
        3. and now 3

          -

          with a continuation

          -
            -
          1. sublist with roman numerals, starting with 4
          2. -
          3. more items -
              -
            1. a subsublist
            2. -
            3. a subsublist
            -
          -
        + - begins with 2 + - and now 3 +with a continuation + - sublist with roman numerals, starting with 4 + - more items + - a subsublist + - a subsublist Nesting: -
          -
        1. Upper Alpha -
            -
          1. Upper Roman. -
              -
            1. Decimal start with 6 -
                -
              1. Lower alpha with paren
              -
            -
          -
        + - Upper Alpha + - Upper Roman. + - Decimal start with 6 + - Lower alpha with paren Autonumbering: -- cgit v1.2.3 From ebcd90b24ad86e734b78dba8c4f544ec4ae5782b Mon Sep 17 00:00:00 2001 From: claremacrae Date: Mon, 19 Aug 2013 21:28:17 +0100 Subject: Fix some warnings in dokuwiki writer (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 0f62e98c3..321e8f428 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -275,8 +275,8 @@ definitionListItemToDokuWiki opts (label, items) = do isSimpleList :: Block -> Bool isSimpleList x = case x of - BulletList items -> True - OrderedList (num, sty, _) items -> True + BulletList _ -> True + OrderedList _ _ -> True DefinitionList items -> all isSimpleListItem $ concatMap snd items _ -> False -- cgit v1.2.3 From 78ae3c24929e02710ef55614694435ecb1029390 Mon Sep 17 00:00:00 2001 From: claremacrae Date: Wed, 28 Aug 2013 08:09:42 +0100 Subject: Implement definition lists in dokuwiki writer (#386) - credit: James Smaldon --- src/Text/Pandoc/Writers/DokuWiki.hs | 55 ++++++++++++++++--------------------- tests/writer.dokuwiki | 21 ++++++++------ 2 files changed, 36 insertions(+), 40 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 321e8f428..41e4d7a8f 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -32,7 +32,6 @@ DokuWiki: {- [ ] Don't generate
        ... - [ ] Implement definition lists [ ] Don't generate lists using
          and
            [ ] Don't generate
            [ ] Implement alignment of text in tables @@ -54,7 +53,7 @@ import Control.Monad.State data WriterState = WriterState { stNotes :: Bool -- True if there are notes - , stListLevel :: [Char] -- String at beginning of list items, e.g. "**" + , stIndent :: String -- Indent after the marker at the beginning of list items , stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list } @@ -62,7 +61,7 @@ data WriterState = WriterState { writeDokuWiki :: WriterOptions -> Pandoc -> String writeDokuWiki opts document = evalState (pandocToDokuWiki opts document) - (WriterState { stNotes = False, stListLevel = [], stUseTags = False }) + (WriterState { stNotes = False, stIndent = "", stUseTags = False }) -- | Return DokuWiki representation of document. pandocToDokuWiki :: WriterOptions -> Pandoc -> State WriterState String @@ -112,11 +111,11 @@ blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToDokuWiki opts (Para inlines) = do useTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + indent <- get >>= return . stIndent contents <- inlineListToDokuWiki opts inlines return $ if useTags then "

            " ++ contents ++ "

            " - else contents ++ if null listLevel then "\n" else "" + else contents ++ if null indent then "\n" else "" blockToDokuWiki _ (RawBlock "mediawiki" str) = return str blockToDokuWiki _ (RawBlock "html" str) = return str @@ -166,7 +165,7 @@ blockToDokuWiki opts (Table capt aligns _ headers rows') = do blockToDokuWiki opts x@(BulletList items) = do oldUseTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + indent <- get >>= return . stIndent let useTags = oldUseTags || not (isSimpleList x) if useTags then do @@ -175,14 +174,14 @@ blockToDokuWiki opts x@(BulletList items) = do modify $ \s -> s { stUseTags = oldUseTags } return $ "
              \n" ++ vcat contents ++ "
            \n" else do - modify $ \s -> s { stListLevel = stListLevel s ++ " " } + modify $ \s -> s { stIndent = stIndent s ++ " " } contents <- mapM (listItemToDokuWiki opts) items - modify $ \s -> s { stListLevel = init (stListLevel s) } - return $ vcat contents ++ if null listLevel then "\n" else "" + modify $ \s -> s { stIndent = indent } + return $ vcat contents ++ if null indent then "\n" else "" blockToDokuWiki opts x@(OrderedList attribs items) = do oldUseTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + indent <- get >>= return . stIndent let useTags = oldUseTags || not (isSimpleList x) if useTags then do @@ -191,17 +190,17 @@ blockToDokuWiki opts x@(OrderedList attribs items) = do modify $ \s -> s { stUseTags = oldUseTags } return $ "\n" ++ vcat contents ++ "
        \n" else do - modify $ \s -> s { stListLevel = stListLevel s ++ " " } + modify $ \s -> s { stIndent = stIndent s ++ " " } contents <- mapM (orderedListItemToDokuWiki opts) items - modify $ \s -> s { stListLevel = init (stListLevel s) } - return $ vcat contents ++ if null listLevel then "\n" else "" + modify $ \s -> s { stIndent = indent } + return $ vcat contents ++ if null indent then "\n" else "" -- TODO Need to decide how to make definition lists work on dokuwiki - I don't think there -- is a specific representation of them. -- TODO This creates double '; ; ' if there is a bullet or ordered list inside a definition list blockToDokuWiki opts x@(DefinitionList items) = do oldUseTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + indent <- get >>= return . stIndent let useTags = oldUseTags || not (isSimpleList x) if useTags then do @@ -210,10 +209,10 @@ blockToDokuWiki opts x@(DefinitionList items) = do modify $ \s -> s { stUseTags = oldUseTags } return $ "
        \n" ++ vcat contents ++ "
        \n" else do - modify $ \s -> s { stListLevel = stListLevel s ++ ";" } + modify $ \s -> s { stIndent = stIndent s ++ " " } contents <- mapM (definitionListItemToDokuWiki opts) items - modify $ \s -> s { stListLevel = init (stListLevel s) } - return $ vcat contents ++ if null listLevel then "\n" else "" + modify $ \s -> s { stIndent = indent } + return $ vcat contents ++ if null indent then "\n" else "" -- Auxiliary functions for lists: @@ -236,10 +235,8 @@ listItemToDokuWiki opts items = do if useTags then return $ "
      • " ++ contents ++ "
      • " else do - marker <- get >>= return . stListLevel - -- This marker ++ marker is an awful hack to write 2 spaces per indentation level. - -- I couldn't find a cleaner way of doing it. - return $ marker ++ marker ++ "* " ++ contents + indent <- get >>= return . stIndent + return $ indent ++ "* " ++ contents -- | Convert ordered list item (list of blocks) to DokuWiki. -- | TODO Emiminate dreadful duplication of text from listItemToDokuWiki @@ -250,10 +247,8 @@ orderedListItemToDokuWiki opts items = do if useTags then return $ "
      • " ++ contents ++ "
      • " else do - marker <- get >>= return . stListLevel - -- This marker ++ marker is an awful hack to write 2 spaces per indentation level. - -- I couldn't find a cleaner way of doing it. - return $ marker ++ marker ++ "- " ++ contents + indent <- get >>= return . stIndent + return $ indent ++ "- " ++ contents -- | Convert definition list item (label, list of blocks) to DokuWiki. definitionListItemToDokuWiki :: WriterOptions @@ -267,9 +262,8 @@ definitionListItemToDokuWiki opts (label, items) = do then return $ "
        " ++ labelText ++ "
        \n" ++ (intercalate "\n" $ map (\d -> "
        " ++ d ++ "
        ") contents) else do - marker <- get >>= return . stListLevel - return $ marker ++ " " ++ labelText ++ "\n" ++ - (intercalate "\n" $ map (\d -> init marker ++ ": " ++ d) contents) + indent <- get >>= return . stIndent + return $ indent ++ "* **" ++ labelText ++ "** " ++ concat contents -- | True if the list can be handled by simple wiki markup, False if HTML tags will be needed. isSimpleList :: Block -> Bool @@ -277,7 +271,7 @@ isSimpleList x = case x of BulletList _ -> True OrderedList _ _ -> True - DefinitionList items -> all isSimpleListItem $ concatMap snd items + DefinitionList _ -> True _ -> False -- | True if list item can be handled with the simple wiki syntax. False if @@ -371,8 +365,7 @@ blockListToDokuWiki opts blocks = -- | Convert list of Pandoc inline elements to DokuWiki. inlineListToDokuWiki :: WriterOptions -> [Inline] -> State WriterState String -inlineListToDokuWiki opts lst = - mapM (inlineToDokuWiki opts) lst >>= return . concat +inlineListToDokuWiki opts lst = mapM (inlineToDokuWiki opts) lst >>= return . concat -- | Convert Pandoc inline element to DokuWiki. inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index bacece683..132c2d614 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -247,25 +247,28 @@ Loose: Multiple blocks with italics: - * **apple** red fruitcontains seeds, crisp, pleasant to taste - * **orange** orange fruit -{ orange code block } -orange block quote + * **//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 + * **apple** red fruitcomputer * **orange** orange fruitbank Multiple definitions, loose: - * **apple** red fruit computer - * **orange** orange fruit bank + * **apple** red fruitcomputer + * **orange** orange fruitbank Blank line after term, indented marker, alternate markers: - * **apple** red fruit computer - * **orange** orange fruit sublist sublist + * **apple** red fruitcomputer + * **orange** orange fruit + - sublist + - sublist ====== HTML Blocks ====== -- cgit v1.2.3 From fdbf52b1cca7d923924ef5d970d946ba6369d6c5 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Sun, 29 Jun 2014 21:15:17 +0100 Subject: Updated DokuWiki code and tests to work with latest code from jgm. The new code was got from inspecting changes in MediaWiki.hs This slightly changes the output of Div blocks, but I'm not convinced the original behaviour was really correct anyway. The code for handling Span does nothing for now, until I can work out the desired behaviour, and add tests for it. --- src/Text/Pandoc/Writers/DokuWiki.hs | 28 ++++++++++++++++++++++------ tests/writer.dokuwiki | 12 +++--------- 2 files changed, 25 insertions(+), 15 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 41e4d7a8f..59c883b55 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -31,6 +31,7 @@ DokuWiki: -} {- + [ ] Correct handling of Span [ ] Don't generate
        ... [ ] Don't generate lists using
          and
            [ ] Don't generate
            @@ -46,6 +47,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared +import Text.Pandoc.Pretty (render) import Text.Pandoc.Templates (renderTemplate') import Data.List ( intersect, intercalate ) import Network.URI ( isURI ) @@ -95,6 +97,11 @@ blockToDokuWiki :: WriterOptions -- ^ Options blockToDokuWiki _ Null = return "" +blockToDokuWiki opts (Div attrs bs) = do + contents <- blockListToDokuWiki opts bs + return $ render Nothing (tagWithAttrs "div" attrs) ++ "\n" ++ + contents ++ "\n" ++ "
            " + blockToDokuWiki opts (Plain inlines) = inlineListToDokuWiki opts inlines @@ -117,9 +124,10 @@ blockToDokuWiki opts (Para inlines) = do then "

            " ++ contents ++ "

            " else contents ++ if null indent then "\n" else "" -blockToDokuWiki _ (RawBlock "mediawiki" str) = return str -blockToDokuWiki _ (RawBlock "html" str) = return str -blockToDokuWiki _ (RawBlock _ _) = return "" +blockToDokuWiki _ (RawBlock f str) + | f == Format "mediawiki" = return str + | f == Format "html" = return str + | otherwise = return "" blockToDokuWiki _ HorizontalRule = return "\n----\n" @@ -370,6 +378,13 @@ inlineListToDokuWiki opts lst = mapM (inlineToDokuWiki opts) lst >>= return . co -- | Convert Pandoc inline element to DokuWiki. inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String +inlineToDokuWiki opts (Span attrs ils) = do + return "" + {- + contents <- inlineListToDokuWiki opts ils + return $ render Nothing (tagWithAttrs "span" attrs) ++ contents ++ "" + -} + inlineToDokuWiki opts (Emph lst) = do contents <- inlineListToDokuWiki opts lst return $ "//" ++ contents ++ "//" @@ -419,9 +434,10 @@ inlineToDokuWiki _ (Str str) = return $ escapeString str inlineToDokuWiki _ (Math _ str) = return $ "" ++ str ++ "" -- note: str should NOT be escaped -inlineToDokuWiki _ (RawInline "mediawiki" str) = return str -inlineToDokuWiki _ (RawInline "html" str) = return str -inlineToDokuWiki _ (RawInline _ _) = return "" +inlineToDokuWiki _ (RawInline f str) + | f == Format "mediawiki" = return str + | f == Format "html" = return str + | otherwise = return "" inlineToDokuWiki _ (LineBreak) = return "\\\\ " diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 132c2d614..b60e57f07 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -277,7 +277,6 @@ Simple block on one line:
            foo
            - And nested without indentation:
            @@ -290,7 +289,6 @@ foo bar
        - Interpreted markdown in a table: @@ -309,10 +307,8 @@ And this is **strong** Here’s a simple block:
        - foo
        - This should be a code block, though:
        @@ -324,14 +320,12 @@ As should this: Now, nested:
        -
        -
        - +
        +
        foo
        -
        - +
        This should just be an HTML comment: -- cgit v1.2.3 From e35738a3cc1f102e5e380639ae89dea1f549a02e Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Sun, 29 Jun 2014 21:21:00 +0100 Subject: Updated Copyright year, for consistency with MediaWiki.hs --- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 59c883b55..1f2a4e33a 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2010 John MacFarlane +Copyright (C) 2008-2014 John MacFarlane 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 @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.DokuWiki - Copyright : Copyright (C) 2008-2010 John MacFarlane + Copyright : Copyright (C) 2008-2014 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane -- cgit v1.2.3 From a049a60129fe12b2b9132d36c9990dbbca3fd4c8 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Mon, 30 Jun 2014 22:07:17 +0100 Subject: Disable warnings about unused parameters. --- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 1f2a4e33a..ce8efb281 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -351,7 +351,7 @@ tableItemToDokuWiki :: WriterOptions -> [Block] -> State WriterState String -- TODO Fix celltype and align' defined but not used -tableItemToDokuWiki opts celltype align' item = do +tableItemToDokuWiki opts _celltype _align' item = do let mkcell x = "" ++ x ++ "" contents <- blockListToDokuWiki opts item return $ mkcell contents @@ -378,7 +378,7 @@ inlineListToDokuWiki opts lst = mapM (inlineToDokuWiki opts) lst >>= return . co -- | Convert Pandoc inline element to DokuWiki. inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String -inlineToDokuWiki opts (Span attrs ils) = do +inlineToDokuWiki _opts (Span _attrs _ils) = do return "" {- contents <- inlineListToDokuWiki opts ils -- cgit v1.2.3 From 072757916754a11cc7837d343c5c63ee1585a35b Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Tue, 1 Jul 2014 21:21:09 +0100 Subject: Improved HTML Blocks in DokuWiki output (#386) For example, this fixes the display of a broken table, and it also fixes the various HTML horizontal rules. --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 +- tests/writer.dokuwiki | 21 ++++++++++++++------- 2 files changed, 15 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index ce8efb281..ad68425ff 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -126,7 +126,7 @@ blockToDokuWiki opts (Para inlines) = do blockToDokuWiki _ (RawBlock f str) | f == Format "mediawiki" = return str - | f == Format "html" = return str + | f == Format "html" = return $ "\n" ++ str ++ "" | otherwise = return "" blockToDokuWiki _ HorizontalRule = return "\n----\n" diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index b60e57f07..c18e95128 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -291,19 +291,22 @@ bar
        Interpreted markdown in a table: +
        - -
        + This is //emphasized// + + And this is **strong** +
        - + Here’s a simple block:
        @@ -328,10 +331,12 @@ foo
        This should just be an HTML comment: + - + Multiline: + - + Code block: Just plain comment, with trailing spaces on the line: + - + Code:
        Hr’s: +

        @@ -370,7 +377,7 @@ Hr’s:

        - + ---- -- cgit v1.2.3 From 244c4eee7487e386e3e6ff7cf78146385eef9d1f Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Tue, 1 Jul 2014 21:42:21 +0100 Subject: Remove stray
        and
        from DokuWiki output (#386) --- src/Text/Pandoc/Writers/DokuWiki.hs | 7 ++----- tests/writer.dokuwiki | 27 +++++++++------------------ 2 files changed, 11 insertions(+), 23 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index ad68425ff..31057f09e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -34,7 +34,6 @@ DokuWiki: [ ] Correct handling of Span [ ] Don't generate
        ... [ ] Don't generate lists using
          and
            - [ ] Don't generate
            [ ] Implement alignment of text in tables [ ] Implement comments [ ] Work through the Dokuwiki spec, and check I've not missed anything out @@ -47,7 +46,6 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared -import Text.Pandoc.Pretty (render) import Text.Pandoc.Templates (renderTemplate') import Data.List ( intersect, intercalate ) import Network.URI ( isURI ) @@ -97,10 +95,9 @@ blockToDokuWiki :: WriterOptions -- ^ Options blockToDokuWiki _ Null = return "" -blockToDokuWiki opts (Div attrs bs) = do +blockToDokuWiki opts (Div _attrs bs) = do contents <- blockListToDokuWiki opts bs - return $ render Nothing (tagWithAttrs "div" attrs) ++ "\n" ++ - contents ++ "\n" ++ "
            " + return $ contents ++ "\n" blockToDokuWiki opts (Plain inlines) = inlineListToDokuWiki opts inlines diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index c18e95128..3e47ee7ee 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -274,21 +274,16 @@ Blank line after term, indented marker, alternate markers: Simple block on one line: -
            foo -
            + And nested without indentation: -
            -
            -
            foo -
            -
            -
            + + bar -
            -
            + + Interpreted markdown in a table: @@ -309,9 +304,8 @@ And this is **strong** Here’s a simple block: -
            foo -
            + This should be a code block, though:
            @@ -322,13 +316,10 @@ As should this:
            foo
            Now, nested: -
            -
            -
            foo -
            -
            -
            + + + This should just be an HTML comment: -- cgit v1.2.3 From 92a962ba63fc8a956cf48a828f200bf10b72cc35 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Wed, 2 Jul 2014 21:01:33 +0100 Subject: DokuWiki writer: remove unused code --- src/Text/Pandoc/Writers/DokuWiki.hs | 25 ------------------------- 1 file changed, 25 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 31057f09e..663bcce2e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -279,31 +279,6 @@ isSimpleList x = DefinitionList _ -> True _ -> False --- | True if list item can be handled with the simple wiki syntax. False if --- HTML tags will be needed. -isSimpleListItem :: [Block] -> Bool -isSimpleListItem [] = True -isSimpleListItem [x] = - case x of - Plain _ -> True - Para _ -> True - BulletList _ -> isSimpleList x - OrderedList _ _ -> isSimpleList x - DefinitionList _ -> isSimpleList x - _ -> False -isSimpleListItem [x, y] | isPlainOrPara x = - case y of - BulletList _ -> isSimpleList y - OrderedList _ _ -> isSimpleList y - DefinitionList _ -> isSimpleList y - _ -> False -isSimpleListItem _ = False - -isPlainOrPara :: Block -> Bool -isPlainOrPara (Plain _) = True -isPlainOrPara (Para _) = True -isPlainOrPara _ = False - -- | Concatenates strings with line breaks between them. vcat :: [String] -> String vcat = intercalate "\n" -- cgit v1.2.3 From d234157d25e13cdb84e96404dfae610c1ad4b4d6 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Wed, 2 Jul 2014 21:26:24 +0100 Subject: DokuWiki output: Implement blockquotes properly TODO Also implement nested blockquotes. --- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- tests/writer.dokuwiki | 24 ++++++++++++------------ 2 files changed, 14 insertions(+), 14 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 663bcce2e..8ea1841eb 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -32,7 +32,7 @@ DokuWiki: {- [ ] Correct handling of Span - [ ] Don't generate
            ... + [ ] Implement nested blockquotes (currently only ever does one level) [ ] Don't generate lists using
              and
                [ ] Implement alignment of text in tables [ ] Implement comments @@ -150,7 +150,7 @@ blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do blockToDokuWiki opts (BlockQuote blocks) = do contents <- blockListToDokuWiki opts blocks - return $ "
                " ++ contents ++ "
                " + return $ "> " ++ contents blockToDokuWiki opts (Table capt aligns _ headers rows') = do let alignStrings = map alignmentToString aligns diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index 3e47ee7ee..b382c5120 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -45,9 +45,9 @@ There should be a hard line break\\ here. E-mail style: -
                This is a block quote. It is pretty short. -
                -
                Code in a block quote: +> This is a block quote. It is pretty short. + +> Code in a block quote: sub status { print "working"; @@ -59,10 +59,10 @@ A list: Nested block quotes: -
                nested -
                -
                nested -
                +> nested + +> nested + This should not be a block quote: 2 > 1. And a following paragraph. @@ -251,7 +251,7 @@ Multiple blocks with italics: contains seeds, crisp, pleasant to taste * **//orange//** orange fruit { orange code block } -
                orange block quote
                +> orange block quote Multiple definitions, tight: @@ -568,8 +568,8 @@ With an ampersand: http://example.com/?foo=1&bar=2 An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]] -
                Blockquoted: http://example.com/ -
                +> Blockquoted: http://example.com/ + Auto-links should not occur here: ''%%%%'' or here: @@ -599,9 +599,9 @@ If you want, you can indent every line, but you can also be lazy and just indent )) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ''%%]%%'' verbatim characters, as well as [bracketed text]. )) -
                Notes can go in quotes.((In quote. +> Notes can go in quotes.((In quote. )) -
                + - And in list items.((In list.)) This paragraph should not be part of the note, as it is not indented. -- cgit v1.2.3 From 61cc983bea706eb4ce7cedcc61824f8dc39c226f Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Wed, 2 Jul 2014 21:40:12 +0100 Subject: DokuWiki writer: Retain unknown RawBlock and RawInline text This added \cite and \begin latex to the testuite output. --- src/Text/Pandoc/Writers/DokuWiki.hs | 4 ++-- tests/writer.dokuwiki | 8 ++++++-- 2 files changed, 8 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 8ea1841eb..621cc77dd 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -124,7 +124,7 @@ blockToDokuWiki opts (Para inlines) = do blockToDokuWiki _ (RawBlock f str) | f == Format "mediawiki" = return str | f == Format "html" = return $ "\n" ++ str ++ "" - | otherwise = return "" + | otherwise = return str blockToDokuWiki _ HorizontalRule = return "\n----\n" @@ -409,7 +409,7 @@ inlineToDokuWiki _ (Math _ str) = return $ "" ++ str ++ "" inlineToDokuWiki _ (RawInline f str) | f == Format "mediawiki" = return str | f == Format "html" = return str - | otherwise = return "" + | otherwise = return str inlineToDokuWiki _ (LineBreak) = return "\\\\ " diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index b382c5120..dc23da1e2 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -424,7 +424,7 @@ Ellipses…and…and…. ====== LaTeX ====== - * + * \cite[22-23]{smith.1899} * 2+2=4 * x \in y * \alpha \wedge \omega @@ -442,7 +442,11 @@ These shouldn’t be math: Here’s a LaTeX table: - +\begin{tabular}{|l|l|}\hline +Animal & Number \\ \hline +Dog & 2 \\ +Cat & 1 \\ \hline +\end{tabular} ---- -- cgit v1.2.3 From 3faf31678ec565bf7bd916ec0bd6e662ffe3123f Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Wed, 2 Jul 2014 21:44:05 +0100 Subject: DokuWiki writer: Remove todos that I have already done. --- src/Text/Pandoc/Writers/DokuWiki.hs | 2 -- 1 file changed, 2 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 621cc77dd..76a0463eb 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -33,11 +33,9 @@ DokuWiki: {- [ ] Correct handling of Span [ ] Implement nested blockquotes (currently only ever does one level) - [ ] Don't generate lists using
                  and
                    [ ] Implement alignment of text in tables [ ] Implement comments [ ] Work through the Dokuwiki spec, and check I've not missed anything out - [ ] Test the output in Dokuwiki - and compare against the display of another format, e.g. HTML [ ] Remove dud/duplicate code -} -- cgit v1.2.3 From 0c6f06b8a493bf9bc578a0b882939bac130e16f0 Mon Sep 17 00:00:00 2001 From: Clare Macrae Date: Wed, 2 Jul 2014 22:40:34 +0100 Subject: DokuWiki writer: Span no longer swallows text --- src/Text/Pandoc/Writers/DokuWiki.hs | 8 ++------ tests/dokuwiki.inline_formatting.dokuwiki | 2 +- 2 files changed, 3 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc/Writers') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 76a0463eb..ea56ac393 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -31,7 +31,6 @@ DokuWiki: -} {- - [ ] Correct handling of Span [ ] Implement nested blockquotes (currently only ever does one level) [ ] Implement alignment of text in tables [ ] Implement comments @@ -348,12 +347,9 @@ inlineListToDokuWiki opts lst = mapM (inlineToDokuWiki opts) lst >>= return . co -- | Convert Pandoc inline element to DokuWiki. inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String -inlineToDokuWiki _opts (Span _attrs _ils) = do - return "" - {- +inlineToDokuWiki opts (Span _attrs ils) = do contents <- inlineListToDokuWiki opts ils - return $ render Nothing (tagWithAttrs "span" attrs) ++ contents ++ "" - -} + return contents inlineToDokuWiki opts (Emph lst) = do contents <- inlineListToDokuWiki opts lst diff --git a/tests/dokuwiki.inline_formatting.dokuwiki b/tests/dokuwiki.inline_formatting.dokuwiki index 2faf49eec..e02596e6c 100644 --- a/tests/dokuwiki.inline_formatting.dokuwiki +++ b/tests/dokuwiki.inline_formatting.dokuwiki @@ -2,7 +2,7 @@ Regular text //italics// **bold //bold italics//**. This is Small Caps, and this is strikethrough. -Some people use . +Some people use single underlines for //emphasis//. Above the line is superscript and below the line is subscript. -- cgit v1.2.3