From 0bc900e36a2c9385ff0163c77993d58fd753d512 Mon Sep 17 00:00:00 2001
From: Matej Kollar <208115@mail.muni.cz>
Date: Mon, 30 Jun 2014 08:38:16 +0200
Subject: HLint suggestions.
---
src/Text/Pandoc/Writers/MediaWiki.hs | 69 ++++++++++++++++++------------------
1 file changed, 34 insertions(+), 35 deletions(-)
(limited to 'src/Text/Pandoc')
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 6a0c2d0e8..edd9771a4 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -37,14 +37,14 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Pretty (render)
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML )
-import Data.List ( intersect, intercalate, intersperse )
+import Data.List ( intersect, intercalate )
import Network.URI ( isURI )
import Control.Monad.Reader
import Control.Monad.State
data WriterState = WriterState {
stNotes :: Bool -- True if there are notes
- , stListLevel :: [Char] -- String at beginning of list items, e.g. "**"
+ , stListLevel :: String -- String at beginning of list items, e.g. "**"
, stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list
}
@@ -65,17 +65,16 @@ pandocToMediaWiki (Pandoc meta blocks) = do
inlineListToMediaWiki
meta
body <- blockListToMediaWiki blocks
- notesExist <- get >>= return . stNotes
+ notesExist <- gets stNotes
let notes = if notesExist
then "\n
" ++ contents ++ "
" @@ -152,14 +151,14 @@ blockToMediaWiki (Table capt aligns widths headers rows') = do return $ "|+ " ++ trimr c ++ "\n" let headless = all null headers let allrows = if headless then rows' else headers:rows' - tableBody <- (concat . intersperse "|-\n") `fmap` + tableBody <- intercalate "|-\n" `fmap` mapM (tableRowToMediaWiki headless aligns widths) (zip [1..] allrows) return $ "{|\n" ++ caption ++ tableBody ++ "|}\n" blockToMediaWiki x@(BulletList items) = do - oldUseTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + oldUseTags <- gets stUseTags + listLevel <- gets stListLevel let useTags = oldUseTags || not (isSimpleList x) if useTags then do @@ -174,8 +173,8 @@ blockToMediaWiki x@(BulletList items) = do return $ vcat contents ++ if null listLevel then "\n" else "" blockToMediaWiki x@(OrderedList attribs items) = do - oldUseTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + oldUseTags <- gets stUseTags + listLevel <- gets stListLevel let useTags = oldUseTags || not (isSimpleList x) if useTags then do @@ -190,8 +189,8 @@ blockToMediaWiki x@(OrderedList attribs items) = do return $ vcat contents ++ if null listLevel then "\n" else "" blockToMediaWiki x@(DefinitionList items) = do - oldUseTags <- get >>= return . stUseTags - listLevel <- get >>= return . stListLevel + oldUseTags <- gets stUseTags + listLevel <- gets stListLevel let useTags = oldUseTags || not (isSimpleList x) if useTags then do @@ -222,11 +221,11 @@ listAttribsToString (startnum, numstyle, _) = listItemToMediaWiki :: [Block] -> MediaWikiWriter String listItemToMediaWiki items = do contents <- blockListToMediaWiki items - useTags <- get >>= return . stUseTags + useTags <- gets stUseTags if useTags then return $ "" ++ (escapeString str) ++ "
"
+ return $ "" ++ escapeString str ++ "
"
inlineToMediaWiki (Str str) = return $ escapeString str
@@ -391,19 +389,20 @@ inlineToMediaWiki (Link txt (src, _)) = do
label <- inlineListToMediaWiki txt
case txt of
[Str s] | escapeURI s == src -> return src
- _ -> if isURI src
- then return $ "[" ++ src ++ " " ++ label ++ "]"
- else return $ "[[" ++ src' ++ "|" ++ label ++ "]]"
+ _ -> return $ if isURI src
+ then "[" ++ src ++ " " ++ label ++ "]"
+ else "[[" ++ src' ++ "|" ++ label ++ "]]"
where src' = case src of
'/':xs -> xs -- with leading / it's a
_ -> src -- link to a help page
+
inlineToMediaWiki (Image alt (source, tit)) = do
alt' <- inlineListToMediaWiki alt
- let txt = if (null tit)
+ let txt = if null tit
then if null alt
then ""
- else "|" ++ alt'
- else "|" ++ tit
+ else '|' : alt'
+ else '|' : tit
return $ "[[Image:" ++ source ++ txt ++ "]]"
inlineToMediaWiki (Note contents) = do
--
cgit v1.2.3