aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/DokuWiki.hs
diff options
context:
space:
mode:
authordespresc <christian.j.j.despres@gmail.com>2019-11-04 16:12:37 -0500
committerJohn MacFarlane <jgm@berkeley.edu>2019-11-12 16:03:45 -0800
commit90e436d49604e3fd1ef9432fb23f6d7f6245c7fd (patch)
tree4e7f0692f989643189f1fc6786050d95e239a0ea /src/Text/Pandoc/Writers/DokuWiki.hs
parentd3966372f5049eea56213b069fc4d70d8af9144c (diff)
downloadpandoc-90e436d49604e3fd1ef9432fb23f6d7f6245c7fd.tar.gz
Switch to new pandoc-types and use Text instead of String [API change].
PR #5884. + Use pandoc-types 1.20 and texmath 0.12. + Text is now used instead of String, with a few exceptions. + In the MediaBag module, some of the types using Strings were switched to use FilePath instead (not Text). + In the Parsing module, new parsers `manyChar`, `many1Char`, `manyTillChar`, `many1TillChar`, `many1Till`, `manyUntil`, `mantyUntilChar` have been added: these are like their unsuffixed counterparts but pack some or all of their output. + `glob` in Text.Pandoc.Class still takes String since it seems to be intended as an interface to Glob, which uses strings. It seems to be used only once in the package, in the EPUB writer, so that is not hard to change.
Diffstat (limited to 'src/Text/Pandoc/Writers/DokuWiki.hs')
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs223
1 files changed, 113 insertions, 110 deletions
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 8111da9ba..541939f3b 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.DokuWiki
Copyright : Copyright (C) 2008-2019 John MacFarlane
@@ -27,15 +28,16 @@ import Control.Monad (zipWithM)
import Control.Monad.Reader (ReaderT, asks, local, runReaderT)
import Control.Monad.State.Strict (StateT, evalStateT)
import Data.Default (Default (..))
-import Data.List (intercalate, intersect, isPrefixOf, transpose)
-import Data.Text (Text, pack)
+import Data.List (intersect, transpose)
+import Data.Text (Text)
+import qualified Data.Text as T
import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText))
import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, isURI, linesToPara,
- removeFormatting, substitute, trimr)
+ removeFormatting, trimr, tshow)
import Text.Pandoc.Templates (renderTemplate)
import Text.DocLayout (render, literal)
import Text.Pandoc.Writers.Shared (defField, metaToContext)
@@ -44,7 +46,7 @@ data WriterState = WriterState {
}
data WriterEnvironment = WriterEnvironment {
- stIndent :: String -- Indent after the marker at the beginning of list items
+ 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)
}
@@ -72,57 +74,58 @@ pandocToDokuWiki :: PandocMonad m
=> WriterOptions -> Pandoc -> DokuWiki m Text
pandocToDokuWiki opts (Pandoc meta blocks) = do
metadata <- metaToContext opts
- (fmap (literal . pack . trimr) . blockListToDokuWiki opts)
- (fmap (literal . pack . trimr) . inlineListToDokuWiki opts)
+ (fmap (literal . trimr) . blockListToDokuWiki opts)
+ (fmap (literal . trimr) . inlineListToDokuWiki opts)
meta
body <- blockListToDokuWiki opts blocks
- let main = pack body
- let context = defField "body" main
+ let context = defField "body" body
$ defField "toc" (writerTableOfContents opts) metadata
return $
case writerTemplate opts of
- Nothing -> main
+ Nothing -> body
Just tpl -> render Nothing $ renderTemplate tpl context
-- | Escape special characters for DokuWiki.
-escapeString :: String -> String
-escapeString = substitute "__" "%%__%%" .
- substitute "**" "%%**%%" .
- substitute "//" "%%//%%"
+escapeString :: Text -> Text
+escapeString = T.replace "__" "%%__%%" .
+ T.replace "**" "%%**%%" .
+ T.replace "//" "%%//%%"
-- | Convert Pandoc block element to DokuWiki.
blockToDokuWiki :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> DokuWiki m String
+ -> DokuWiki m Text
blockToDokuWiki _ Null = return ""
blockToDokuWiki opts (Div _attrs bs) = do
contents <- blockListToDokuWiki opts bs
- return $ contents ++ "\n"
+ return $ contents <> "\n"
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 attr txt (src,'f':'i':'g':':':tit)]) = do
- capt <- if null txt
- then return ""
- else (" " ++) `fmap` inlineListToDokuWiki opts txt
- let opt = if null txt
- then ""
- else "|" ++ if null tit then capt else tit ++ capt
- return $ "{{" ++ src ++ imageDims opts attr ++ opt ++ "}}\n"
+blockToDokuWiki opts (Para [Image attr txt (src,tgt)])
+ | Just tit <- T.stripPrefix "fig:" tgt
+ = do
+ capt <- if null txt
+ then return ""
+ else (" " <>) `fmap` inlineListToDokuWiki opts txt
+ let opt = if null txt
+ then ""
+ else "|" <> if T.null tit then capt else tit <> capt
+ return $ "{{" <> src <> imageDims opts attr <> opt <> "}}\n"
blockToDokuWiki opts (Para inlines) = do
indent <- asks stIndent
useTags <- asks stUseTags
contents <- inlineListToDokuWiki opts inlines
return $ if useTags
- then "<HTML><p></HTML>" ++ contents ++ "<HTML></p></HTML>"
- else contents ++ if null indent then "\n" else ""
+ then "<HTML><p></HTML>" <> contents <> "<HTML></p></HTML>"
+ else contents <> if T.null indent then "\n" else ""
blockToDokuWiki opts (LineBlock lns) =
blockToDokuWiki opts $ linesToPara lns
@@ -131,7 +134,7 @@ blockToDokuWiki _ 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 $ "<HTML>\n" ++ str ++ "\n</HTML>"
+ | f == Format "html" = return $ "<HTML>\n" <> str <> "\n</HTML>"
| otherwise = "" <$
report (BlockNotRendered b)
@@ -141,8 +144,8 @@ blockToDokuWiki opts (Header level _ inlines) = do
-- emphasis, links etc. not allowed in headers, apparently,
-- so we remove formatting:
contents <- inlineListToDokuWiki opts $ removeFormatting inlines
- let eqs = replicate ( 7 - level ) '='
- return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n"
+ let eqs = T.replicate ( 7 - level ) "="
+ return $ eqs <> " " <> contents <> " " <> eqs <> "\n"
blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do
let at = classes `intersect` ["actionscript", "ada", "apache", "applescript", "asm", "asp",
@@ -154,43 +157,43 @@ blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do
"python", "qbasic", "rails", "reg", "robots", "ruby", "sas", "scheme", "sdlbasic",
"smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl",
"visualfoxpro", "winbatch", "xml", "xpp", "z80"]
- return $ "<code" ++
+ return $ "<code" <>
(case at of
[] -> ">\n"
- (x:_) -> " " ++ x ++ ">\n") ++ str ++ "\n</code>"
+ (x:_) -> " " <> x <> ">\n") <> str <> "\n</code>"
blockToDokuWiki opts (BlockQuote blocks) = do
contents <- blockListToDokuWiki opts blocks
if isSimpleBlockQuote blocks
- then return $ unlines $ map ("> " ++) $ lines contents
- else return $ "<HTML><blockquote>\n" ++ contents ++ "</blockquote></HTML>"
+ then return $ T.unlines $ map ("> " <>) $ T.lines contents
+ else return $ "<HTML><blockquote>\n" <> contents <> "</blockquote></HTML>"
blockToDokuWiki opts (Table capt aligns _ headers rows) = do
captionDoc <- if null capt
then return ""
else do
c <- inlineListToDokuWiki opts capt
- return $ "" ++ c ++ "\n"
+ return $ "" <> c <> "\n"
headers' <- if all null headers
then return []
else zipWithM (tableItemToDokuWiki opts) aligns headers
rows' <- mapM (zipWithM (tableItemToDokuWiki opts) aligns) rows
- let widths = map (maximum . map length) $ transpose (headers':rows')
+ let widths = map (maximum . map T.length) $ transpose (headers':rows')
let padTo (width, al) s =
- case width - length s of
+ case width - T.length s of
x | x > 0 ->
if al == AlignLeft || al == AlignDefault
- then s ++ replicate x ' '
+ then s <> T.replicate x " "
else if al == AlignRight
- then replicate x ' ' ++ s
- else replicate (x `div` 2) ' ' ++
- s ++ replicate (x - x `div` 2) ' '
+ then T.replicate x " " <> s
+ else T.replicate (x `div` 2) " " <>
+ s <> T.replicate (x - x `div` 2) " "
| otherwise -> s
- let renderRow sep cells = sep ++
- intercalate sep (zipWith padTo (zip widths aligns) cells) ++ sep
- return $ captionDoc ++
- (if null headers' then "" else renderRow "^" headers' ++ "\n") ++
- unlines (map (renderRow "|") rows')
+ let renderRow sep cells = sep <>
+ T.intercalate sep (zipWith padTo (zip widths aligns) cells) <> sep
+ return $ captionDoc <>
+ (if null headers' then "" else renderRow "^" headers' <> "\n") <>
+ T.unlines (map (renderRow "|") rows')
blockToDokuWiki opts x@(BulletList items) = do
oldUseTags <- asks stUseTags
@@ -201,12 +204,12 @@ blockToDokuWiki opts x@(BulletList items) = do
then do
contents <- local (\s -> s { stUseTags = True })
(mapM (listItemToDokuWiki opts) items)
- return $ "<HTML><ul></HTML>\n" ++ vcat contents ++ "<HTML></ul></HTML>\n"
+ return $ "<HTML><ul></HTML>\n" <> vcat contents <> "<HTML></ul></HTML>\n"
else do
- contents <- local (\s -> s { stIndent = stIndent s ++ " "
+ contents <- local (\s -> s { stIndent = stIndent s <> " "
, stBackSlashLB = backSlash})
(mapM (listItemToDokuWiki opts) items)
- return $ vcat contents ++ if 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
@@ -217,12 +220,12 @@ blockToDokuWiki opts x@(OrderedList attribs items) = do
then do
contents <- local (\s -> s { stUseTags = True })
(mapM (orderedListItemToDokuWiki opts) items)
- return $ "<HTML><ol" ++ listAttribsToString attribs ++ "></HTML>\n" ++ vcat contents ++ "<HTML></ol></HTML>\n"
+ return $ "<HTML><ol" <> listAttribsToString attribs <> "></HTML>\n" <> vcat contents <> "<HTML></ol></HTML>\n"
else do
- contents <- local (\s -> s { stIndent = stIndent s ++ " "
+ contents <- local (\s -> s { stIndent = stIndent s <> " "
, stBackSlashLB = backSlash})
(mapM (orderedListItemToDokuWiki opts) items)
- return $ vcat contents ++ if null indent then "\n" else ""
+ return $ vcat contents <> if T.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.
@@ -236,76 +239,76 @@ blockToDokuWiki opts x@(DefinitionList items) = do
then do
contents <- local (\s -> s { stUseTags = True })
(mapM (definitionListItemToDokuWiki opts) items)
- return $ "<HTML><dl></HTML>\n" ++ vcat contents ++ "<HTML></dl></HTML>\n"
+ return $ "<HTML><dl></HTML>\n" <> vcat contents <> "<HTML></dl></HTML>\n"
else do
- contents <- local (\s -> s { stIndent = stIndent s ++ " "
+ contents <- local (\s -> s { stIndent = stIndent s <> " "
, stBackSlashLB = backSlash})
(mapM (definitionListItemToDokuWiki opts) items)
- return $ vcat contents ++ if null indent then "\n" else ""
+ return $ vcat contents <> if T.null indent then "\n" else ""
-- Auxiliary functions for lists:
-- | Convert ordered list attributes to HTML attribute string
-listAttribsToString :: ListAttributes -> String
+listAttribsToString :: ListAttributes -> Text
listAttribsToString (startnum, numstyle, _) =
- let numstyle' = camelCaseToHyphenated $ show numstyle
+ let numstyle' = camelCaseToHyphenated $ tshow numstyle
in (if startnum /= 1
- then " start=\"" ++ show startnum ++ "\""
- else "") ++
+ then " start=\"" <> tshow startnum <> "\""
+ else "") <>
(if numstyle /= DefaultStyle
- then " style=\"list-style-type: " ++ numstyle' ++ ";\""
+ then " style=\"list-style-type: " <> numstyle' <> ";\""
else "")
-- | Convert bullet list item (list of blocks) to DokuWiki.
listItemToDokuWiki :: PandocMonad m
- => WriterOptions -> [Block] -> DokuWiki m String
+ => WriterOptions -> [Block] -> DokuWiki m Text
listItemToDokuWiki opts items = do
useTags <- asks stUseTags
if useTags
then do
contents <- blockListToDokuWiki opts items
- return $ "<HTML><li></HTML>" ++ contents ++ "<HTML></li></HTML>"
+ return $ "<HTML><li></HTML>" <> contents <> "<HTML></li></HTML>"
else do
bs <- mapM (blockToDokuWiki opts) items
let contents = case items of
- [_, CodeBlock _ _] -> concat bs
+ [_, CodeBlock _ _] -> T.concat bs
_ -> vcat bs
indent <- asks stIndent
backSlash <- asks stBackSlashLB
- let indent' = if backSlash then drop 2 indent else indent
- return $ indent' ++ "* " ++ contents
+ let indent' = if backSlash then T.drop 2 indent else indent
+ return $ indent' <> "* " <> 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 String
+orderedListItemToDokuWiki :: PandocMonad m => WriterOptions -> [Block] -> DokuWiki m Text
orderedListItemToDokuWiki opts items = do
contents <- blockListToDokuWiki opts items
useTags <- asks stUseTags
if useTags
- then return $ "<HTML><li></HTML>" ++ contents ++ "<HTML></li></HTML>"
+ then return $ "<HTML><li></HTML>" <> contents <> "<HTML></li></HTML>"
else do
indent <- asks stIndent
backSlash <- asks stBackSlashLB
- let indent' = if backSlash then drop 2 indent else indent
- return $ indent' ++ "- " ++ contents
+ let indent' = if backSlash then T.drop 2 indent else indent
+ return $ indent' <> "- " <> contents
-- | Convert definition list item (label, list of blocks) to DokuWiki.
definitionListItemToDokuWiki :: PandocMonad m
=> WriterOptions
-> ([Inline],[[Block]])
- -> DokuWiki m String
+ -> DokuWiki m Text
definitionListItemToDokuWiki opts (label, items) = do
labelText <- inlineListToDokuWiki opts label
contents <- mapM (blockListToDokuWiki opts) items
useTags <- asks stUseTags
if useTags
- then return $ "<HTML><dt></HTML>" ++ labelText ++ "<HTML></dt></HTML>\n" ++
- intercalate "\n" (map (\d -> "<HTML><dd></HTML>" ++ d ++ "<HTML></dd></HTML>") contents)
+ then return $ "<HTML><dt></HTML>" <> labelText <> "<HTML></dt></HTML>\n" <>
+ T.intercalate "\n" (map (\d -> "<HTML><dd></HTML>" <> d <> "<HTML></dd></HTML>") contents)
else do
indent <- asks stIndent
backSlash <- asks stBackSlashLB
- let indent' = if backSlash then drop 2 indent else indent
- return $ indent' ++ "* **" ++ labelText ++ "** " ++ concat contents
+ 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
@@ -333,17 +336,17 @@ isSimpleBlockQuote :: [Block] -> Bool
isSimpleBlockQuote bs = all isPlainOrPara bs
-- | Concatenates strings with line breaks between them.
-vcat :: [String] -> String
-vcat = intercalate "\n"
+vcat :: [Text] -> Text
+vcat = T.intercalate "\n"
-- | 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
+backSlashLineBreaks :: [Text] -> Text
+backSlashLineBreaks ls = vcatBackSlash $ map (T.pack . escape . T.unpack) ls
where
- vcatBackSlash = intercalate "\\\\ \\\\ " -- simulate paragraphs.
- escape ['\n'] = "" -- remove trailing newlines
- escape ('\n':cs) = "\\\\ " ++ escape cs
+ vcatBackSlash = T.intercalate "\\\\ \\\\ " -- simulate paragraphs.
+ escape ['\n'] = "" -- remove trailing newlines
+ escape ('\n':cs) = "\\\\ " <> escape cs
escape (c:cs) = c : escape cs
escape [] = []
@@ -353,11 +356,11 @@ tableItemToDokuWiki :: PandocMonad m
=> WriterOptions
-> Alignment
-> [Block]
- -> DokuWiki m String
+ -> DokuWiki m Text
tableItemToDokuWiki opts align' item = do
let mkcell x = (if align' == AlignRight || align' == AlignCenter
then " "
- else "") ++ x ++
+ else "") <> x <>
(if align' == AlignLeft || align' == AlignCenter
then " "
else "")
@@ -369,7 +372,7 @@ tableItemToDokuWiki opts align' item = do
blockListToDokuWiki :: PandocMonad m
=> WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> DokuWiki m String
+ -> DokuWiki m Text
blockListToDokuWiki opts blocks = do
backSlash <- asks stBackSlashLB
let blocks' = consolidateRawBlocks blocks
@@ -380,51 +383,51 @@ blockListToDokuWiki opts blocks = do
consolidateRawBlocks :: [Block] -> [Block]
consolidateRawBlocks [] = []
consolidateRawBlocks (RawBlock f1 b1 : RawBlock f2 b2 : xs)
- | f1 == f2 = consolidateRawBlocks (RawBlock f1 (b1 ++ "\n" ++ b2) : xs)
+ | f1 == f2 = consolidateRawBlocks (RawBlock f1 (b1 <> "\n" <> b2) : xs)
consolidateRawBlocks (x:xs) = x : consolidateRawBlocks xs
-- | Convert list of Pandoc inline elements to DokuWiki.
inlineListToDokuWiki :: PandocMonad m
- => WriterOptions -> [Inline] -> DokuWiki m String
+ => WriterOptions -> [Inline] -> DokuWiki m Text
inlineListToDokuWiki opts lst =
- concat <$> mapM (inlineToDokuWiki opts) lst
+ T.concat <$> mapM (inlineToDokuWiki opts) lst
-- | Convert Pandoc inline element to DokuWiki.
inlineToDokuWiki :: PandocMonad m
- => WriterOptions -> Inline -> DokuWiki m String
+ => WriterOptions -> Inline -> DokuWiki m Text
inlineToDokuWiki opts (Span _attrs ils) =
inlineListToDokuWiki opts ils
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
- return $ "<del>" ++ contents ++ "</del>"
+ return $ "<del>" <> contents <> "</del>"
inlineToDokuWiki opts (Superscript lst) = do
contents <- inlineListToDokuWiki opts lst
- return $ "<sup>" ++ contents ++ "</sup>"
+ return $ "<sup>" <> contents <> "</sup>"
inlineToDokuWiki opts (Subscript lst) = do
contents <- inlineListToDokuWiki opts lst
- return $ "<sub>" ++ contents ++ "</sub>"
+ return $ "<sub>" <> contents <> "</sub>"
inlineToDokuWiki opts (SmallCaps lst) = inlineListToDokuWiki opts lst
inlineToDokuWiki opts (Quoted SingleQuote lst) = do
contents <- inlineListToDokuWiki opts lst
- return $ "\8216" ++ contents ++ "\8217"
+ return $ "\8216" <> contents <> "\8217"
inlineToDokuWiki opts (Quoted DoubleQuote lst) = do
contents <- inlineListToDokuWiki opts lst
- return $ "\8220" ++ contents ++ "\8221"
+ return $ "\8220" <> contents <> "\8221"
inlineToDokuWiki opts (Cite _ lst) = inlineListToDokuWiki opts lst
@@ -438,11 +441,11 @@ inlineToDokuWiki _ (Code _ str) =
-- 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 ++ "%%''"
+ return $ "''%%" <> str <> "%%''"
inlineToDokuWiki _ (Str str) = return $ escapeString str
-inlineToDokuWiki _ (Math mathType str) = return $ delim ++ str ++ delim
+inlineToDokuWiki _ (Math mathType str) = return $ delim <> str <> delim
-- note: str should NOT be escaped
where delim = case mathType of
DisplayMath -> "$$"
@@ -450,7 +453,7 @@ inlineToDokuWiki _ (Math mathType str) = return $ delim ++ str ++ delim
inlineToDokuWiki _ il@(RawInline f str)
| f == Format "dokuwiki" = return str
- | f == Format "html" = return $ "<html>" ++ str ++ "</html>"
+ | f == Format "html" = return $ "<html>" <> str <> "</html>"
| otherwise = "" <$ report (InlineNotRendered il)
inlineToDokuWiki _ LineBreak = do
@@ -470,34 +473,34 @@ inlineToDokuWiki _ Space = return " "
inlineToDokuWiki opts (Link _ txt (src, _)) = do
label <- inlineListToDokuWiki opts txt
case txt of
- [Str s] | "mailto:" `isPrefixOf` src -> return $ "<" ++ s ++ ">"
+ [Str s] | "mailto:" `T.isPrefixOf` src -> return $ "<" <> 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
+ then return $ "[[" <> src <> "|" <> label <> "]]"
+ else return $ "[[" <> src' <> "|" <> label <> "]]"
+ where src' = case T.uncons src of
+ Just ('/',xs) -> xs -- with leading / it's a
+ _ -> src -- link to a help page
inlineToDokuWiki opts (Image attr alt (source, tit)) = do
alt' <- inlineListToDokuWiki opts alt
let txt = case (tit, alt) of
("", []) -> ""
- ("", _ ) -> "|" ++ alt'
- (_ , _ ) -> "|" ++ tit
- return $ "{{" ++ source ++ imageDims opts attr ++ txt ++ "}}"
+ ("", _ ) -> "|" <> alt'
+ (_ , _ ) -> "|" <> tit
+ return $ "{{" <> source <> imageDims opts attr <> txt <> "}}"
inlineToDokuWiki opts (Note contents) = do
contents' <- blockListToDokuWiki opts contents
- return $ "((" ++ contents' ++ "))"
+ return $ "((" <> contents' <> "))"
-- note - may not work for notes with multiple blocks
-imageDims :: WriterOptions -> Attr -> String
+imageDims :: WriterOptions -> Attr -> Text
imageDims opts attr = go (toPx $ dimension Width attr) (toPx $ dimension Height attr)
where
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
checkPct maybeDim = maybeDim
- go (Just w) Nothing = "?" ++ w
- go (Just w) (Just h) = "?" ++ w ++ "x" ++ h
- go Nothing (Just h) = "?0x" ++ h
+ go (Just w) Nothing = "?" <> w
+ go (Just w) (Just h) = "?" <> w <> "x" <> h
+ go Nothing (Just h) = "?0x" <> h
go Nothing Nothing = ""