diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 24e256fa6fc0..70097756f8e0 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -643,7 +643,8 @@ getAllExtensions f = universalExtensions <> getAll f getAll "vimwiki" = autoIdExtensions getAll "dokuwiki" = autoIdExtensions <> extensionsFromList - [ Ext_tex_math_dollars ] + [ Ext_tex_math_dollars + , Ext_raw_html ] getAll "tikiwiki" = autoIdExtensions getAll "rst" = autoIdExtensions <> extensionsFromList diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index f0aa6e4504de..34ea2e3bd76e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -14,7 +14,7 @@ DokuWiki: -} {- - [ ] Implement nested blockquotes (currently only ever does one level) + [x] Implement nested blockquotes (currently only ever does one level) [x] Implement alignment of text in tables [ ] Implement comments [ ] Work through the Dokuwiki spec, and check I've not missed anything out @@ -32,12 +32,12 @@ import Data.Text (Text) import qualified Data.Text as T import Text.Pandoc.Class.PandocMonad (PandocMonad, report) import Text.Pandoc.Definition +import Text.Pandoc.Extensions import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, - writerTemplate, writerWrapText)) -import Text.Pandoc.Shared (camelCaseToHyphenated, figureDiv, linesToPara, - removeFormatting, trimr, tshow) + writerTemplate, writerWrapText), isEnabled) +import Text.Pandoc.Shared (figureDiv, linesToPara, removeFormatting, trimr) import Text.Pandoc.URI (escapeURI, isURI) import Text.Pandoc.Templates (renderTemplate) import Text.DocLayout (render, literal) @@ -50,8 +50,8 @@ data WriterState = WriterState { data WriterEnvironment = WriterEnvironment { stIndent :: Text -- 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 , stBackSlashLB :: Bool -- True if we should produce formatted strings with newlines (as in a table cell) + , stBlockQuoteLevel :: Int -- Block quote level } instance Default WriterState where @@ -59,8 +59,8 @@ instance Default WriterState where instance Default WriterEnvironment where def = WriterEnvironment { stIndent = "" - , stUseTags = False - , stBackSlashLB = False } + , stBackSlashLB = False + , stBlockQuoteLevel = 0 } type DokuWiki m = ReaderT WriterEnvironment (StateT WriterState m) @@ -109,21 +109,23 @@ blockToDokuWiki opts (Plain inlines) = inlineListToDokuWiki opts inlines blockToDokuWiki opts (Para inlines) = do + bqLevel <- asks stBlockQuoteLevel + let bqPrefix = case bqLevel of + 0 -> "" + n -> T.replicate n ">" <> " " indent <- asks stIndent - useTags <- asks stUseTags contents <- inlineListToDokuWiki opts inlines - return $ if useTags - then "

" <> contents <> "

" - else contents <> if T.null indent then "\n" else "" + return $ bqPrefix <> contents <> if T.null indent then "\n" else "" blockToDokuWiki opts (LineBlock lns) = blockToDokuWiki opts $ linesToPara lns -blockToDokuWiki _ b@(RawBlock f str) +blockToDokuWiki opts b@(RawBlock f str) | f == Format "dokuwiki" = return str -- See https://www.dokuwiki.org/wiki:syntax -- use uppercase HTML tag for block-level content: - | f == Format "html" = return $ "\n" <> str <> "\n" + | f == Format "html" + , isEnabled Ext_raw_html opts = return $ "\n" <> str <> "\n" | otherwise = "" <$ report (BlockNotRendered b) @@ -136,19 +138,22 @@ blockToDokuWiki opts (Header level _ inlines) = do let eqs = T.replicate ( 7 - level ) "=" return $ eqs <> " " <> contents <> " " <> eqs <> "\n" -blockToDokuWiki _ (CodeBlock (_,classes,_) str) = - return $ " +blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do + bqLevel <- asks stBlockQuoteLevel + let bqPrefix = case bqLevel of + 0 -> "" + n -> T.replicate n ">" <> " " + return $ bqPrefix <> + " (case classes of [] -> "" (x:_) -> " " <> fromMaybe x (M.lookup x languageNames)) <> ">\n" <> str <> (if "\n" `T.isSuffixOf` str then "" else "\n") <> "\n" -blockToDokuWiki opts (BlockQuote blocks) = do - contents <- blockListToDokuWiki opts blocks - if isSimpleBlockQuote blocks - then return $ T.unlines $ map ("> " <>) $ T.lines contents - else return $ "
\n" <> contents <> "
" +blockToDokuWiki opts (BlockQuote blocks) = + local (\st -> st{ stBlockQuoteLevel = stBlockQuoteLevel st + 1 }) + (blockListToDokuWiki opts blocks) blockToDokuWiki opts (Table _ blkCapt specs thead tbody tfoot) = do let (capt, aligns, _, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot @@ -179,37 +184,21 @@ blockToDokuWiki opts (Table _ blkCapt specs thead tbody tfoot) = do (if null headers' then "" else renderRow "^" headers' <> "\n") <> T.unlines (map (renderRow "|") rows') -blockToDokuWiki opts x@(BulletList items) = do - oldUseTags <- asks stUseTags +blockToDokuWiki opts (BulletList items) = do indent <- asks stIndent backSlash <- asks stBackSlashLB - let useTags = oldUseTags || not (isSimpleList x) - if useTags - then do - contents <- local (\s -> s { stUseTags = True }) + contents <- local (\s -> s { stIndent = stIndent s <> " " + , stBackSlashLB = backSlash}) (mapM (listItemToDokuWiki opts) items) - return $ "
    \n" <> vcat contents <> "
\n" - else do - contents <- local (\s -> s { stIndent = stIndent s <> " " - , stBackSlashLB = backSlash}) - (mapM (listItemToDokuWiki opts) items) - return $ vcat contents <> if T.null indent then "\n" else "" + return $ vcat contents <> if T.null indent then "\n" else "" -blockToDokuWiki opts x@(OrderedList attribs items) = do - oldUseTags <- asks stUseTags +blockToDokuWiki opts (OrderedList _attribs items) = do indent <- asks stIndent backSlash <- asks stBackSlashLB - let useTags = oldUseTags || not (isSimpleList x) - if useTags - then do - contents <- local (\s -> s { stUseTags = True }) - (mapM (orderedListItemToDokuWiki opts) items) - return $ " listAttribsToString attribs <> ">\n" <> vcat contents <> "\n" - else do - contents <- local (\s -> s { stIndent = stIndent s <> " " - , stBackSlashLB = backSlash}) - (mapM (orderedListItemToDokuWiki opts) items) - return $ vcat contents <> if T.null indent then "\n" else "" + contents <- local (\s -> s { stIndent = stIndent s <> " " + , stBackSlashLB = backSlash}) + (mapM (orderedListItemToDokuWiki opts) items) + return $ vcat contents <> if T.null indent then "\n" else "" blockToDokuWiki opts (Figure attr capt body) = blockToDokuWiki opts $ figureDiv attr capt body @@ -217,67 +206,55 @@ blockToDokuWiki opts (Figure attr capt body) = -- 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 <- asks stUseTags +blockToDokuWiki opts (DefinitionList items) = do indent <- asks stIndent backSlash <- asks stBackSlashLB - let useTags = oldUseTags || not (isSimpleList x) - if useTags - then do - contents <- local (\s -> s { stUseTags = True }) - (mapM (definitionListItemToDokuWiki opts) items) - return $ "
\n" <> vcat contents <> "
\n" - else do - contents <- local (\s -> s { stIndent = stIndent s <> " " - , stBackSlashLB = backSlash}) - (mapM (definitionListItemToDokuWiki opts) items) - return $ vcat contents <> if T.null indent then "\n" else "" + contents <- local (\s -> s { stIndent = stIndent s <> " " + , stBackSlashLB = backSlash}) + (mapM (definitionListItemToDokuWiki opts) items) + return $ vcat contents <> if T.null indent then "\n" else "" -- Auxiliary functions for lists: --- | Convert ordered list attributes to HTML attribute string -listAttribsToString :: ListAttributes -> Text -listAttribsToString (startnum, numstyle, _) = - let numstyle' = camelCaseToHyphenated $ tshow numstyle - in (if startnum /= 1 - then " start=\"" <> tshow startnum <> "\"" - else "") <> - (if numstyle /= DefaultStyle - then " style=\"list-style-type: " <> numstyle' <> ";\"" - else "") - -- | Convert bullet list item (list of blocks) to DokuWiki. listItemToDokuWiki :: PandocMonad m => WriterOptions -> [Block] -> DokuWiki m Text listItemToDokuWiki opts items = do - useTags <- asks stUseTags - if useTags - then do - contents <- blockListToDokuWiki opts items - return $ "
  • " <> contents <> "
  • " - else do - bs <- mapM (blockToDokuWiki opts) items - let contents = case items of - [_, CodeBlock _ _] -> T.concat bs - _ -> vcat bs - indent <- asks stIndent - backSlash <- asks stBackSlashLB - let indent' = if backSlash then T.drop 2 indent else indent - return $ indent' <> "* " <> contents + bqLevel <- asks stBlockQuoteLevel + let bqPrefix = case bqLevel of + 0 -> "" + n -> T.replicate n ">" <> " " + let useWrap = not (isSimpleListItem items) + bs <- mapM (blockToDokuWiki opts) items + let contents = case items of + [_, CodeBlock _ _] -> T.concat bs + _ -> vcat bs + indent <- asks stIndent + backSlash <- asks stBackSlashLB + let indent' = if backSlash then T.drop 2 indent else indent + return $ bqPrefix <> indent' <> "* " <> + if useWrap + then "\n" <> contents <> "\n" + else contents -- | Convert ordered list item (list of blocks) to DokuWiki. -- | TODO Emiminate dreadful duplication of text from listItemToDokuWiki orderedListItemToDokuWiki :: PandocMonad m => WriterOptions -> [Block] -> DokuWiki m Text orderedListItemToDokuWiki opts items = do - contents <- blockListToDokuWiki opts items - useTags <- asks stUseTags - if useTags - then return $ "
  • " <> contents <> "
  • " - else do - indent <- asks stIndent - backSlash <- asks stBackSlashLB - let indent' = if backSlash then T.drop 2 indent else indent - return $ indent' <> "- " <> contents + bqLevel <- asks stBlockQuoteLevel + let bqPrefix = case bqLevel of + 0 -> "" + n -> T.replicate n ">" <> " " + let useWrap = not (isSimpleListItem items) + contents <- local (\st -> st{ stBlockQuoteLevel = 0 }) + (blockListToDokuWiki opts items) + indent <- asks stIndent + backSlash <- asks stBackSlashLB + let indent' = if backSlash then T.drop 2 indent else indent + return $ bqPrefix <> indent' <> "- " <> + if useWrap + then "\n" <> contents <> "\n" + else contents -- | Convert definition list item (label, list of blocks) to DokuWiki. definitionListItemToDokuWiki :: PandocMonad m @@ -285,29 +262,24 @@ definitionListItemToDokuWiki :: PandocMonad m -> ([Inline],[[Block]]) -> DokuWiki m Text definitionListItemToDokuWiki opts (label, items) = do + let useWrap = not (all isSimpleListItem items) + bqLevel <- asks stBlockQuoteLevel + let bqPrefix = case bqLevel of + 0 -> "" + n -> T.replicate n ">" <> " " labelText <- inlineListToDokuWiki opts label - contents <- mapM (blockListToDokuWiki opts) items - useTags <- asks stUseTags - if useTags - then return $ "
    " <> labelText <> "
    \n" <> - T.intercalate "\n" (map (\d -> "
    " <> d <> "
    ") contents) - else do - indent <- asks stIndent - backSlash <- asks stBackSlashLB - let indent' = if backSlash then T.drop 2 indent else indent - return $ indent' <> "* **" <> labelText <> "** " <> T.concat 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 (1, _, _) items -> all isSimpleListItem items - DefinitionList items -> all (all isSimpleListItem . snd) items - _ -> False + contents <- local (\st -> st{ stBlockQuoteLevel = 0 }) + (mapM (blockListToDokuWiki opts) items) + indent <- asks stIndent + backSlash <- asks stBackSlashLB + let indent' = if backSlash then T.drop 2 indent else indent + return $ bqPrefix <> indent' <> "* **" <> labelText <> "** " <> + if useWrap + then "\n" <> vcat contents <> "\n" + else T.intercalate "; " contents -- | True if list item can be handled with the simple wiki syntax. False if --- HTML tags will be needed. +-- WRAP tags will be needed. isSimpleListItem :: [Block] -> Bool isSimpleListItem [] = True isSimpleListItem [x, CodeBlock{}] | isPlainOrPara x = True @@ -315,15 +287,21 @@ isSimpleListItem (Div _ bs : ys) = -- see #8920 isSimpleListItem bs && all isSimpleList ys isSimpleListItem (x:ys) | isPlainOrPara x = all isSimpleList ys isSimpleListItem _ = False +--- | 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 (1, _, _) items -> all isSimpleListItem items + DefinitionList items -> all (all isSimpleListItem . snd) items + _ -> False isPlainOrPara :: Block -> Bool isPlainOrPara (Plain _) = True isPlainOrPara (Para _) = True isPlainOrPara _ = False -isSimpleBlockQuote :: [Block] -> Bool -isSimpleBlockQuote bs = all isPlainOrPara bs - -- | Concatenates strings with line breaks between them. vcat :: [Text] -> Text vcat = T.intercalate "\n" @@ -353,8 +331,9 @@ tableItemToDokuWiki opts align' item = do (if align' == AlignLeft || align' == AlignCenter then " " else "") - contents <- local (\s -> s { stBackSlashLB = True }) $ - blockListToDokuWiki opts item + contents <- local (\s -> s { stBackSlashLB = True + , stBlockQuoteLevel = 0 }) $ + blockListToDokuWiki opts item return $ mkcell contents -- | Convert list of Pandoc block elements to DokuWiki. @@ -444,9 +423,10 @@ inlineToDokuWiki _ (Math mathType str) = return $ delim <> str <> delim DisplayMath -> "$$" InlineMath -> "$" -inlineToDokuWiki _ il@(RawInline f str) +inlineToDokuWiki opts il@(RawInline f str) | f == Format "dokuwiki" = return str - | f == Format "html" = return $ "" <> str <> "" + | f == Format "html" + , isEnabled Ext_raw_html opts = return $ "" <> str <> "" | otherwise = "" <$ report (InlineNotRendered il) inlineToDokuWiki _ LineBreak = do @@ -483,7 +463,8 @@ inlineToDokuWiki opts (Image attr alt (source, tit)) = do return $ "{{" <> source <> imageDims opts attr <> txt <> "}}" inlineToDokuWiki opts (Note contents) = do - contents' <- blockListToDokuWiki opts contents + contents' <- local (\st -> st{ stBlockQuoteLevel = 0 }) + (blockListToDokuWiki opts contents) return $ "((" <> contents' <> "))" -- note - may not work for notes with multiple blocks diff --git a/test/writer.dokuwiki b/test/writer.dokuwiki index bb47524f3bbf..57f1bf19f54f 100644 --- a/test/writer.dokuwiki +++ b/test/writer.dokuwiki @@ -48,26 +48,25 @@ E-mail style: > This is a block quote. It is pretty short. -
    -Code in a block quote: +> Code in a block quote: - +> sub status { print "working"; } -A list: +> A list: + +> - item one +> - item two - - item one - - item two +> Nested block quotes: -Nested block quotes: +>> nested -> nested +>> nested -> nested -
    This should not be a block quote: 2 > 1. And a following paragraph. @@ -168,11 +167,12 @@ 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 ===== @@ -207,32 +207,28 @@ 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: @@ -271,32 +267,32 @@ Loose: Multiple blocks with italics: -
    -
    //apple//
    -

    red fruit

    -

    contains seeds, crisp, pleasant to taste

    -
    //orange//
    -

    orange fruit

    + * **//apple//** +red fruit +contains seeds, crisp, pleasant to taste + + * **//orange//** +orange fruit { orange code block } ->

    orange block quote

    -
    +> orange block quote + Multiple definitions, tight: - * **apple** red fruitcomputer - * **orange** orange fruitbank + * **apple** red fruit; computer + * **orange** orange fruit; bank Multiple definitions, loose: - * **apple** red fruitcomputer - * **orange** orange fruitbank + * **apple** red fruit; computer + * **orange** orange fruit; bank Blank line after term, indented marker, alternate markers: - * **apple** red fruitcomputer + * **apple** red fruit; computer * **orange** orange fruit - sublist - sublist @@ -318,23 +314,11 @@ bar Interpreted markdown in a table: - - - - - - -
    - + This is //emphasized// - - - + And this is **strong** - -
    - - + Here’s a simple block: foo @@ -362,20 +346,10 @@ foo This should just be an HTML comment: - - - + Multiline: - - - - + Code block: @@ -384,9 +358,7 @@ Code block: Just plain comment, with trailing spaces on the line: - - - + Code: @@ -395,17 +367,7 @@ Code: Hr’s: - -
    -
    -
    -
    -
    -
    -
    -
    -
    - + ---- @@ -644,7 +606,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.))