diff options
Diffstat (limited to 'src/Text/Pandoc/Writers/DokuWiki.hs')
-rw-r--r-- | src/Text/Pandoc/Writers/DokuWiki.hs | 26 |
1 files changed, 18 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index dda21d23d..189bf138e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {- Copyright (C) 2008-2018 John MacFarlane <jgm@berkeley.edu> @@ -39,6 +40,7 @@ DokuWiki: <https://www.dokuwiki.org/dokuwiki> -} module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where +import Prelude import Control.Monad (zipWithM) import Control.Monad.Reader (ReaderT, ask, local, runReaderT) import Control.Monad.State.Strict (StateT, evalStateT) @@ -366,12 +368,16 @@ isSimpleBlockQuote bs = all isPlainOrPara bs vcat :: [String] -> String vcat = intercalate "\n" -backSlashLineBreaks :: String -> String -backSlashLineBreaks cs = reverse $ g $ reverse $ concatMap f cs - where f '\n' = "\\\\ " - f c = [c] - g (' ' : '\\':'\\': xs) = xs - g s = s +-- | For each string in the input list, convert all newlines to +-- dokuwiki escaped newlines. Then concat the list using double linebreaks. +backSlashLineBreaks :: [String] -> String +backSlashLineBreaks ls = vcatBackSlash $ map escape ls + where + vcatBackSlash = intercalate "\\\\ \\\\ " -- simulate paragraphs. + escape ['\n'] = "" -- remove trailing newlines + escape ('\n':cs) = "\\\\ " ++ escape cs + escape (c:cs) = c : escape cs + escape [] = [] -- Auxiliary functions for tables: @@ -400,7 +406,7 @@ blockListToDokuWiki opts blocks = do backSlash <- stBackSlashLB <$> ask let blocks' = consolidateRawBlocks blocks if backSlash - then (backSlashLineBreaks . vcat) <$> mapM (blockToDokuWiki opts) blocks' + then backSlashLineBreaks <$> mapM (blockToDokuWiki opts) blocks' else vcat <$> mapM (blockToDokuWiki opts) blocks' consolidateRawBlocks :: [Block] -> [Block] @@ -479,7 +485,11 @@ inlineToDokuWiki _ il@(RawInline f str) | f == Format "html" = return $ "<html>" ++ str ++ "</html>" | otherwise = "" <$ report (InlineNotRendered il) -inlineToDokuWiki _ LineBreak = return "\\\\\n" +inlineToDokuWiki _ LineBreak = do + backSlash <- stBackSlashLB <$> ask + return $ if backSlash + then "\n" + else "\\\\\n" inlineToDokuWiki opts SoftBreak = case writerWrapText opts of |