From 1ed2c467c9442934c060257f6e191a5a3d6c1e38 Mon Sep 17 00:00:00 2001
From: Henry de Valence <hdevalence@hdevalence.ca>
Date: Thu, 19 Dec 2013 17:06:27 -0500
Subject: [PATCH 1/6] HLint: Use all

Replace `and . map` with `all`.
---
 src/Text/Pandoc/Shared.hs        | 2 +-
 src/Text/Pandoc/Writers/LaTeX.hs | 8 ++++----
 2 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index ce71881e6..cd2f7e24d 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -532,7 +532,7 @@ headerShift n = walk shift
 
 -- | Detect if a list is tight.
 isTightList :: [[Block]] -> Bool
-isTightList = and . map firstIsPlain
+isTightList = all firstIsPlain
   where firstIsPlain (Plain _ : _) = True
         firstIsPlain _             = False
 
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 7612be100..47b769c48 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -443,7 +443,7 @@ blockToLaTeX (DefinitionList lst) = do
   incremental <- gets stIncremental
   let inc = if incremental then "[<+->]" else ""
   items <- mapM defListItemToLaTeX lst
-  let spacing = if and $ map isTightList (map snd lst)
+  let spacing = if all isTightList (map snd lst)
                    then text "\\itemsep1pt\\parskip0pt\\parsep0pt"
                    else empty
   return $ text ("\\begin{description}" ++ inc) $$ spacing $$ vcat items $$
@@ -764,9 +764,9 @@ citationsToNatbib cits
   | noPrefix (tail cits) && noSuffix (init cits) && ismode NormalCitation cits
   = citeCommand "citep" p s ks
   where
-     noPrefix  = and . map (null . citationPrefix)
-     noSuffix  = and . map (null . citationSuffix)
-     ismode m  = and . map (((==) m)  . citationMode)
+     noPrefix  = all (null . citationPrefix)
+     noSuffix  = all (null . citationSuffix)
+     ismode m  = all (((==) m)  . citationMode)
      p         = citationPrefix  $ head $ cits
      s         = citationSuffix  $ last $ cits
      ks        = intercalate ", " $ map citationId cits

From 0c5e7cf8cb4fe6959d7e89880e8925afe6625414 Mon Sep 17 00:00:00 2001
From: Henry de Valence <hdevalence@hdevalence.ca>
Date: Thu, 19 Dec 2013 20:19:24 -0500
Subject: [PATCH 2/6] HLint: use `elem` and `notElem`

Replaces long conditional chains with calls to `elem` and `notElem`.
---
 pandoc.hs                           |  2 +-
 src/Text/Pandoc/Parsing.hs          |  4 ++--
 src/Text/Pandoc/Readers/LaTeX.hs    |  5 ++---
 src/Text/Pandoc/Readers/Markdown.hs |  8 ++++----
 src/Text/Pandoc/Shared.hs           | 12 ++++--------
 src/Text/Pandoc/Writers/Markdown.hs | 11 ++++++-----
 src/Text/Pandoc/Writers/Org.hs      |  2 +-
 7 files changed, 20 insertions(+), 24 deletions(-)

diff --git a/pandoc.hs b/pandoc.hs
index cada3347d..ccd3e57fb 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -656,7 +656,7 @@ options =
                  (ReqArg
                   (\arg opt -> do
                      let b = takeBaseName arg
-                     if (b == "pdflatex" || b == "lualatex" || b == "xelatex")
+                     if b `elem` ["pdflatex", "lualatex", "xelatex"]
                         then return opt { optLaTeXEngine = arg }
                         else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.")
                   "PROGRAM")
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index e15854333..2f21e1253 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -271,7 +271,7 @@ spaceChar = satisfy $ \c -> c == ' ' || c == '\t'
 
 -- | Parses a nonspace, nonnewline character.
 nonspaceChar :: Parser [Char] st Char
-nonspaceChar = satisfy $ \x -> x /= '\t' && x /= '\n' && x /= ' ' && x /= '\r'
+nonspaceChar = satisfy $ flip notElem ['\t', '\n', ' ', '\r']
 
 -- | Skips zero or more spaces or tabs.
 skipSpaces :: Parser [Char] st ()
@@ -1062,7 +1062,7 @@ doubleQuoteStart :: Parser [Char] ParserState ()
 doubleQuoteStart = do
   failIfInQuoteContext InDoubleQuote
   try $ do charOrRef "\"\8220\147"
-           notFollowedBy (satisfy (\c -> c == ' ' || c == '\t' || c == '\n'))
+           notFollowedBy . satisfy $ flip elem [' ', '\t', '\n']
 
 doubleQuoteEnd :: Parser [Char] st ()
 doubleQuoteEnd = do
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 0020a8f26..51271edc5 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -874,9 +874,8 @@ verbatimEnv = do
   (_,r) <- withRaw $ do
              controlSeq "begin"
              name <- braced
-             guard $ name == "verbatim" || name == "Verbatim" ||
-                     name == "lstlisting" || name == "minted" ||
-                     name == "alltt"
+             guard $ name `elem` ["verbatim", "Verbatim", "lstlisting",
+                                  "minted", "alltt"]
              verbEnv name
   rest <- getInput
   return (r,rest)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index b2e88d47e..f483ab059 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -789,8 +789,8 @@ listItem start = try $ do
 orderedList :: MarkdownParser (F Blocks)
 orderedList = try $ do
   (start, style, delim) <- lookAhead anyOrderedListStart
-  unless ((style == DefaultStyle || style == Decimal || style == Example) &&
-          (delim == DefaultDelim || delim == Period)) $
+  unless (style `elem` [DefaultStyle, Decimal, Example] &&
+          delim `elem` [DefaultDelim, Period]) $
     guardEnabled Ext_fancy_lists
   when (style == Example) $ guardEnabled Ext_example_lists
   items <- fmap sequence $ many1 $ listItem
@@ -925,8 +925,8 @@ strictHtmlBlock = htmlInBalanced (not . isInlineTag)
 
 rawVerbatimBlock :: MarkdownParser String
 rawVerbatimBlock = try $ do
-  (TagOpen tag _, open) <- htmlTag (tagOpen (\t ->
-                              t == "pre" || t == "style" || t == "script")
+  (TagOpen tag _, open) <- htmlTag (tagOpen (flip elem
+                                                  ["pre", "style", "script"])
                               (const True))
   contents <- manyTill anyChar (htmlTag (~== TagClose tag))
   return $ open ++ contents ++ renderTags [TagClose tag]
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index cd2f7e24d..3446f4343 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -564,14 +564,10 @@ makeMeta title authors date =
 -- | Render HTML tags.
 renderTags' :: [Tag String] -> String
 renderTags' = renderTagsOptions
-               renderOptions{ optMinimize = \x ->
-                                    let y = map toLower x
-                                    in  y == "hr" || y == "br" ||
-                                        y == "img" || y == "meta" ||
-                                        y == "link"
-                            , optRawTag = \x ->
-                                    let y = map toLower x
-                                    in  y == "script" || y == "style" }
+               renderOptions{ optMinimize = matchTags ["hr", "br", "img",
+                                                       "meta", "link"]
+                            , optRawTag   = matchTags ["script", "style"] }
+              where matchTags = \tags -> flip elem tags . map toLower
 
 --
 -- File handling
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index c0b189b75..278e5cc9d 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -338,7 +338,7 @@ blockToMarkdown opts (RawBlock f str)
        else return $ if isEnabled Ext_markdown_attribute opts
                         then text (addMarkdownAttribute str) <> text "\n"
                         else text str <> text "\n"
-  | f == "latex" || f == "tex" || f == "markdown" = do
+  | f `elem` ["latex", "tex", "markdown"] = do
     st <- get
     if stPlain st
        then return empty
@@ -628,10 +628,11 @@ getReference label (src, tit) = do
     Nothing       -> do
       let label' = case find ((== label) . fst) (stRefs st) of
                       Just _ -> -- label is used; generate numerical label
-                                 case find (\n -> not (any (== [Str (show n)])
-                                           (map fst (stRefs st)))) [1..(10000 :: Integer)] of
-                                      Just x  -> [Str (show x)]
-                                      Nothing -> error "no unique label"
+                             case find (\n -> notElem [Str (show n)]
+                                                      (map fst (stRefs st)))
+                                       [1..(10000 :: Integer)] of
+                                  Just x  -> [Str (show x)]
+                                  Nothing -> error "no unique label"
                       Nothing -> label
       modify (\s -> s{ stRefs = (label', (src,tit)) : stRefs st })
       return label'
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 51083f52b..d318c5f6a 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -129,7 +129,7 @@ blockToOrg (Para inlines) = do
 blockToOrg (RawBlock "html" str) =
   return $ blankline $$ "#+BEGIN_HTML" $$
            nest 2 (text str) $$ "#+END_HTML" $$ blankline
-blockToOrg (RawBlock f str) | f == "org" || f == "latex" || f == "tex" =
+blockToOrg (RawBlock f str) | f `elem` ["org", "latex", "tex"] =
   return $ text str
 blockToOrg (RawBlock _ _) = return empty
 blockToOrg HorizontalRule = return $ blankline $$ "--------------" $$ blankline

From c35f5ba42df094cef5f69a191315385a0a1e12b0 Mon Sep 17 00:00:00 2001
From: Henry de Valence <hdevalence@hdevalence.ca>
Date: Thu, 19 Dec 2013 20:28:53 -0500
Subject: [PATCH 3/6] HLint: Remove lambdas.

---
 src/Text/Pandoc/Writers/Shared.hs | 3 +--
 tests/Tests/Walk.hs               | 4 ++--
 2 files changed, 3 insertions(+), 4 deletions(-)

diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index 9cb08803c..33091ea94 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -65,8 +65,7 @@ metaToJSON opts blockWriter inlineWriter (Meta metamap)
     renderedMap <- Traversable.mapM
                    (metaValueToJSON blockWriter inlineWriter)
                    metamap
-    return $ M.foldWithKey (\key val obj -> defField key val obj)
-                   baseContext renderedMap
+    return $ M.foldWithKey defField baseContext renderedMap
   | otherwise = return (Object H.empty)
 
 metaValueToJSON :: Monad m
diff --git a/tests/Tests/Walk.hs b/tests/Tests/Walk.hs
index f6aa1beae..34350e28a 100644
--- a/tests/Tests/Walk.hs
+++ b/tests/Tests/Walk.hs
@@ -21,11 +21,11 @@ tests = [ testGroup "Walk"
 
 p_walk :: (Typeable a, Walkable a Pandoc)
        => (a -> a) -> Pandoc -> Bool
-p_walk f = (\(d :: Pandoc) -> everywhere (mkT f) d == walk f d)
+p_walk f d = everywhere (mkT f) d == walk f d
 
 p_query :: (Eq a, Typeable a1, Monoid a, Walkable a1 Pandoc)
         => (a1 -> a) -> Pandoc -> Bool
-p_query f = (\(d :: Pandoc) -> everything mappend (mempty `mkQ` f) d == query f d)
+p_query f d = everything mappend (mempty `mkQ` f) d == query f d
 
 inlineTrans :: Inline -> Inline
 inlineTrans (Str xs) = Str $ map toUpper xs

From f6d151889c8fff303be8ee8a4f9be67a04de9210 Mon Sep 17 00:00:00 2001
From: Henry de Valence <hdevalence@hdevalence.ca>
Date: Thu, 19 Dec 2013 20:43:25 -0500
Subject: [PATCH 4/6] HLint: redundant parens

Remove parens enclosing a single element.
---
 pandoc.hs                            | 6 ++----
 src/Text/Pandoc/Readers/Markdown.hs  | 2 +-
 src/Text/Pandoc/Readers/Textile.hs   | 2 +-
 src/Text/Pandoc/Writers/HTML.hs      | 2 +-
 src/Text/Pandoc/Writers/MediaWiki.hs | 2 +-
 src/Text/Pandoc/Writers/Textile.hs   | 2 +-
 tests/Tests/Readers/LaTeX.hs         | 2 +-
 tests/Tests/Readers/Markdown.hs      | 4 ++--
 8 files changed, 10 insertions(+), 12 deletions(-)

diff --git a/pandoc.hs b/pandoc.hs
index ccd3e57fb..574c89771 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1034,12 +1034,10 @@ main = do
 
   variables' <- case mathMethod of
                       LaTeXMathML Nothing -> do
-                         s <- readDataFileUTF8 datadir
-                                 ("LaTeXMathML.js")
+                         s <- readDataFileUTF8 datadir "LaTeXMathML.js"
                          return $ ("mathml-script", s) : variables
                       MathML Nothing -> do
-                         s <- readDataFileUTF8 datadir
-                                 ("MathMLinHTML.js")
+                         s <- readDataFileUTF8 datadir "MathMLinHTML.js"
                          return $ ("mathml-script", s) : variables
                       _ -> return variables
 
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index f483ab059..166c524ef 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -730,7 +730,7 @@ listStart = bulletListStart <|> (anyOrderedListStart >> return ())
 listLine :: MarkdownParser String
 listLine = try $ do
   notFollowedBy' (do indentSpaces
-                     many (spaceChar)
+                     many spaceChar
                      listStart)
   notFollowedBy' $ htmlTag (~== TagClose "div")
   chunks <- manyTill
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 23e07f621..93658cdea 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -594,7 +594,7 @@ surrounded border = enclosed (border *> notFollowedBy (oneOf " \t\n\r")) (try bo
 simpleInline :: Parser [Char] ParserState t           -- ^ surrounding parser
                 -> ([Inline] -> Inline)       -- ^ Inline constructor
                 -> Parser [Char] ParserState Inline   -- ^ content parser (to be used repeatedly)
-simpleInline border construct = surrounded border (inlineWithAttribute) >>=
+simpleInline border construct = surrounded border inlineWithAttribute >>=
                                 return . construct . normalizeSpaces
   where inlineWithAttribute = (try $ optional attributes) >> inline
 
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 641652276..2c6435457 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -524,7 +524,7 @@ blockToHtml opts (DefinitionList lst) = do
   contents <- mapM (\(term, defs) ->
                   do term' <- if null term
                                  then return mempty
-                                 else liftM (H.dt) $ inlineListToHtml opts term
+                                 else liftM H.dt $ inlineListToHtml opts term
                      defs' <- mapM ((liftM (\x -> H.dd $ (x >> nl opts))) .
                                     blockListToHtml opts) defs
                      return $ mconcat $ nl opts : term' : nl opts :
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 61741a61e..83fefaa29 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -51,7 +51,7 @@ data WriterState = WriterState {
 writeMediaWiki :: WriterOptions -> Pandoc -> String
 writeMediaWiki opts document =
   evalState (pandocToMediaWiki opts document)
-            (WriterState { stNotes = False, stListLevel = [], stUseTags = False })
+            WriterState { stNotes = False, stListLevel = [], stUseTags = False }
 
 -- | Return MediaWiki representation of document.
 pandocToMediaWiki :: WriterOptions -> Pandoc -> State WriterState String
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 7c102cc86..95aedf780 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -51,7 +51,7 @@ data WriterState = WriterState {
 writeTextile :: WriterOptions -> Pandoc -> String
 writeTextile opts document =
   evalState (pandocToTextile opts document)
-            (WriterState { stNotes = [], stListLevel = [], stUseTags = False })
+            WriterState { stNotes = [], stListLevel = [], stUseTags = False }
 
 -- | Return Textile representation of document.
 pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index c1efd1b68..8ff23ebc1 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -21,7 +21,7 @@ tests = [ testGroup "basic"
           [ "simple" =:
             "word" =?> para "word"
           , "space" =:
-            "some text" =?> para ("some text")
+            "some text" =?> para "some text"
           , "emphasized" =:
             "\\emph{emphasized}" =?> para (emph "emphasized")
           ]
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index b04ff9a0d..492680a35 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -171,13 +171,13 @@ tests = [ testGroup "inline code"
         , testGroup "smart punctuation"
           [ test markdownSmart "quote before ellipses"
             ("'...hi'"
-            =?> para (singleQuoted ("…hi")))
+            =?> para (singleQuoted "…hi"))
           , test markdownSmart "apostrophe before emph"
             ("D'oh! A l'*aide*!"
             =?> para ("D’oh! A l’" <> emph "aide" <> "!"))
           , test markdownSmart "apostrophe in French"
             ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
-            =?> para ("À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»"))
+            =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
           ]
         , testGroup "mixed emphasis and strong"
           [ "emph and strong emph alternating" =:

From c8fc0a03748ceb4dbea502297ece89eac9d73aff Mon Sep 17 00:00:00 2001
From: Henry de Valence <hdevalence@hdevalence.ca>
Date: Thu, 19 Dec 2013 20:46:11 -0500
Subject: [PATCH 5/6] HLint: use /=

---
 src/Text/Pandoc/Writers/LaTeX.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 47b769c48..1deacecb4 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -190,7 +190,7 @@ stringToLaTeX  _     []     = return ""
 stringToLaTeX  ctx (x:xs) = do
   opts <- gets stOptions
   rest <- stringToLaTeX ctx xs
-  let ligatures = writerTeXLigatures opts && not (ctx == CodeString)
+  let ligatures = writerTeXLigatures opts && (ctx /= CodeString)
   let isUrl = ctx == URLString
   when (x == '€') $
      modify $ \st -> st{ stUsesEuro = True }

From 3d70059a4896c66cab59832a3ed9eb8334b84a2f Mon Sep 17 00:00:00 2001
From: Henry de Valence <hdevalence@hdevalence.ca>
Date: Thu, 19 Dec 2013 21:07:09 -0500
Subject: [PATCH 6/6] HLint: use fromMaybe

Replace uses of `maybe x id` with `fromMaybe x`.
---
 src/Text/Pandoc/PDF.hs               |  3 ++-
 src/Text/Pandoc/Readers/DocBook.hs   |  7 ++++---
 src/Text/Pandoc/Readers/HTML.hs      |  4 ++--
 src/Text/Pandoc/Readers/Markdown.hs  |  4 ++--
 src/Text/Pandoc/Readers/MediaWiki.hs |  7 ++++---
 src/Text/Pandoc/Writers/Docx.hs      |  6 ++++--
 src/Text/Pandoc/Writers/EPUB.hs      | 12 ++++++------
 src/Text/Pandoc/Writers/HTML.hs      |  4 ++--
 src/Text/Pandoc/Writers/LaTeX.hs     |  3 ++-
 src/Text/Pandoc/Writers/ODT.hs       |  3 ++-
 10 files changed, 30 insertions(+), 23 deletions(-)

diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index e8683b98f..360338f8f 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -41,6 +41,7 @@ import System.Directory
 import System.Environment
 import Control.Monad (unless)
 import Data.List (isInfixOf)
+import Data.Maybe (fromMaybe)
 import qualified Data.ByteString.Base64 as B64
 import qualified Text.Pandoc.UTF8 as UTF8
 import Text.Pandoc.Definition
@@ -87,7 +88,7 @@ handleImage' baseURL tmpdir (Image ils (src,tit)) = do
          res <- fetchItem baseURL src
          case res of
               Right (contents, Just mime) -> do
-                let ext = maybe (takeExtension src) id $
+                let ext = fromMaybe (takeExtension src) $
                           extensionFromMimeType mime
                 let basename = UTF8.toString $ B64.encode $ UTF8.fromString src
                 let fname = tmpdir </> basename <.> ext
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 03c6140ac..56cb16b20 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -12,6 +12,7 @@ import Data.Char (isSpace)
 import Control.Monad.State
 import Control.Applicative ((<$>))
 import Data.List (intersperse)
+import Data.Maybe (fromMaybe)
 
 {-
 
@@ -683,7 +684,7 @@ parseBlock (Elem e) =
                                "lowerroman" -> LowerRoman
                                "upperroman" -> UpperRoman
                                _            -> Decimal
-          let start = maybe 1 id $
+          let start = fromMaybe 1 $
                       (attrValue "override" <$> filterElement (named "listitem") e)
                        >>= safeRead
           orderedListWith (start,listStyle,DefaultDelim)
@@ -779,7 +780,7 @@ parseBlock (Elem e) =
                       caption <- case filterChild isCaption e of
                                        Just t  -> getInlines t
                                        Nothing -> return mempty
-                      let e' = maybe e id $ filterChild (named "tgroup") e
+                      let e' = fromMaybe e $ filterChild (named "tgroup") e
                       let isColspec x = named "colspec" x || named "col" x
                       let colspecs = case filterChild (named "colgroup") e' of
                                            Just c -> filterChildren isColspec c
@@ -801,7 +802,7 @@ parseBlock (Elem e) =
                                                 Just "center" -> AlignCenter
                                                 _             -> AlignDefault
                       let toWidth c = case findAttr (unqual "colwidth") c of
-                                                Just w -> maybe 0 id
+                                                Just w -> fromMaybe 0
                                                    $ safeRead $ '0': filter (\x ->
                                                      (x >= '0' && x <= '9')
                                                       || x == '.') w
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index e758f712f..4b44a3a21 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -207,7 +207,7 @@ pHeader = try $ do
   let bodyTitle = TagOpen tagtype attr ~== TagOpen "h1" [("class","title")]
   let level = read (drop 1 tagtype)
   contents <- liftM concat $ manyTill inline (pCloses tagtype <|> eof)
-  let ident = maybe "" id $ lookup "id" attr
+  let ident = fromMaybe "" $ lookup "id" attr
   let classes = maybe [] words $ lookup "class" attr
   let keyvals = [(k,v) | (k,v) <- attr, k /= "class", k /= "id"]
   return $ if bodyTitle
@@ -257,7 +257,7 @@ pCol = try $ do
   skipMany pBlank
   return $ case lookup "width" attribs of
            Just x | not (null x) && last x == '%' ->
-             maybe 0.0 id $ safeRead ('0':'.':init x)
+             fromMaybe 0.0 $ safeRead ('0':'.':init x)
            _ -> 0.0
 
 pColgroup :: TagParser [Double]
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 166c524ef..3a5d29b4e 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1722,7 +1722,7 @@ spanHtml = try $ do
   guardEnabled Ext_markdown_in_html_blocks
   (TagOpen _ attrs, _) <- htmlTag (~== TagOpen "span" [])
   contents <- mconcat <$> manyTill inline (htmlTag (~== TagClose "span"))
-  let ident = maybe "" id $ lookup "id" attrs
+  let ident = fromMaybe "" $ lookup "id" attrs
   let classes = maybe [] words $ lookup "class" attrs
   let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
   return $ B.spanWith (ident, classes, keyvals) <$> contents
@@ -1732,7 +1732,7 @@ divHtml = try $ do
   guardEnabled Ext_markdown_in_html_blocks
   (TagOpen _ attrs, _) <- htmlTag (~== TagOpen "div" [])
   contents <- mconcat <$> manyTill block (htmlTag (~== TagClose "div"))
-  let ident = maybe "" id $ lookup "id" attrs
+  let ident = fromMaybe "" $ lookup "id" attrs
   let classes = maybe [] words $ lookup "class" attrs
   let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
   return $ B.divWith (ident, classes, keyvals) <$> contents
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 1c074e3de..8d8ea0199 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -54,6 +54,7 @@ import Data.Sequence (viewl, ViewL(..), (<|))
 import qualified Data.Foldable as F
 import qualified Data.Map as M
 import Data.Char (isDigit, isSpace)
+import Data.Maybe (fromMaybe)
 
 -- | Read mediawiki from an input string and return a Pandoc document.
 readMediaWiki :: ReaderOptions -- ^ Reader options
@@ -204,7 +205,7 @@ table = do
   tableStart
   styles <- option [] parseAttrs <* blankline
   let tableWidth = case lookup "width" styles of
-                         Just w  -> maybe 1.0 id $ parseWidth w
+                         Just w  -> fromMaybe 1.0 $ parseWidth w
                          Nothing -> 1.0
   caption <- option mempty tableCaption
   optional rowsep
@@ -285,7 +286,7 @@ tableCell = try $ do
                     Just "center" -> AlignCenter
                     _             -> AlignDefault
   let width = case lookup "width" attrs of
-                    Just xs -> maybe 0.0 id $ parseWidth xs
+                    Just xs -> fromMaybe 0.0 $ parseWidth xs
                     Nothing -> 0.0
   return ((align, width), bs)
 
@@ -387,7 +388,7 @@ orderedList =
           spaces
           items <- many (listItem '#' <|> li)
           optional (htmlTag (~== TagClose "ol"))
-          let start = maybe 1 id $ safeRead $ fromAttrib "start" tag
+          let start = fromMaybe 1 $ safeRead $ fromAttrib "start" tag
           return $ B.orderedListWith (start, DefaultStyle, DefaultDelim) items
 
 definitionList :: MWParser Blocks
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 5c7341b69..32ba7715a 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -29,6 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
 Conversion of 'Pandoc' documents to docx.
 -}
 module Text.Pandoc.Writers.Docx ( writeDocx ) where
+import Data.Maybe (fromMaybe)
 import Data.List ( intercalate, groupBy )
 import qualified Data.ByteString as B
 import qualified Data.ByteString.Lazy as BL
@@ -130,7 +131,8 @@ writeDocx opts doc@(Pandoc meta _) = do
   let mkOverrideNode (part', contentType') = mknode "Override"
                [("PartName",part'),("ContentType",contentType')] ()
   let mkImageOverride (_, imgpath, mbMimeType, _, _) =
-             mkOverrideNode ("/word/" ++ imgpath, maybe "application/octet-stream" id mbMimeType)
+             mkOverrideNode ("/word/" ++ imgpath,
+                             fromMaybe "application/octet-stream" mbMimeType)
   let overrides = map mkOverrideNode
                   [("/word/webSettings.xml",
                     "application/vnd.openxmlformats-officedocument.wordprocessingml.webSettings+xml")
@@ -322,7 +324,7 @@ mkNum markers marker numid =
        NumberMarker _ _ start ->
           map (\lvl -> mknode "w:lvlOverride" [("w:ilvl",show (lvl :: Int))]
               $ mknode "w:startOverride" [("w:val",show start)] ()) [0..6]
-   where absnumid = maybe 0 id $ M.lookup marker markers
+   where absnumid = fromMaybe 0 $ M.lookup marker markers
 
 mkAbstractNum :: (ListMarker,Int) -> IO Element
 mkAbstractNum (marker,numid) = do
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 36ead0b8f..4daa9609e 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -176,8 +176,8 @@ addMetadataFromXML e@(Element (QName name _ (Just "dc")) attrs _ _) md
                  , titleFileAs = getAttr "file-as"
                  , titleType = getAttr "type"
                  } : epubTitle md }
-  | name == "date" = md{ epubDate = maybe "" id $ normalizeDate'
-                                                $ strContent e }
+  | name == "date" = md{ epubDate = fromMaybe "" $ normalizeDate'
+                                                 $ strContent e }
   | name == "language" = md{ epubLanguage = strContent e }
   | name == "creator" = md{ epubCreator =
               Creator{ creatorText = strContent e
@@ -271,7 +271,7 @@ metadataFromMeta opts meta = EPUBMetadata{
     }
   where identifiers = getIdentifier meta
         titles = getTitle meta
-        date = maybe "" id $
+        date = fromMaybe "" $
               (metaValueToString <$> lookupMeta "date" meta) >>= normalizeDate'
         language = maybe "" metaValueToString $
            lookupMeta "language" meta `mplus` lookupMeta "lang" meta
@@ -297,7 +297,7 @@ writeEPUB :: WriterOptions  -- ^ Writer options
           -> Pandoc         -- ^ Document to convert
           -> IO B.ByteString
 writeEPUB opts doc@(Pandoc meta _) = do
-  let version = maybe EPUB2 id (writerEpubVersion opts)
+  let version = fromMaybe EPUB2 (writerEpubVersion opts)
   let epub3 = version == EPUB3
   epochtime <- floor `fmap` getPOSIXTime
   let mkEntry path content = toEntry path epochtime content
@@ -401,7 +401,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
       chapToEntry num (Chapter mbnum bs) = mkEntry (showChapter num)
         $ renderHtml
         $ writeHtml opts'{ writerNumberOffset =
-            maybe [] id mbnum }
+            fromMaybe [] mbnum }
         $ case bs of
               (Header _ _ xs : _) ->
                  Pandoc (setMeta "title" (fromList xs) nullMeta) bs
@@ -436,7 +436,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
   let fontNode ent = unode "item" !
                            [("id", takeBaseName $ eRelativePath ent),
                             ("href", eRelativePath ent),
-                            ("media-type", maybe "" id $ getMimeType $ eRelativePath ent)] $ ()
+                            ("media-type", fromMaybe "" $ getMimeType $ eRelativePath ent)] $ ()
   let plainTitle = case docTitle meta of
                         [] -> case epubTitle metadata of
                                    []   -> "UNTITLED"
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 2c6435457..129776363 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -45,7 +45,7 @@ import Numeric ( showHex )
 import Data.Char ( ord, toLower )
 import Data.List ( isPrefixOf, intersperse )
 import Data.String ( fromString )
-import Data.Maybe ( catMaybes )
+import Data.Maybe ( catMaybes, fromMaybe )
 import Control.Monad.State
 import Text.Blaze.Html hiding(contents)
 import Text.Blaze.Internal(preEscapedString)
@@ -118,7 +118,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
   let stringifyHTML = escapeStringForXML . stringify
   let authsMeta = map stringifyHTML $ docAuthors meta
   let dateMeta  = stringifyHTML $ docDate meta
-  let slideLevel = maybe (getSlideLevel blocks) id $ writerSlideLevel opts
+  let slideLevel = fromMaybe (getSlideLevel blocks) $ writerSlideLevel opts
   let sects = hierarchicalize $
               if writerSlideVariant opts == NoSlides
                  then blocks
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 1deacecb4..a76d6d82b 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -40,6 +40,7 @@ import Network.URI ( isURI, unEscapeString )
 import Data.List ( (\\), isSuffixOf, isInfixOf,
                    isPrefixOf, intercalate, intersperse )
 import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit, ord )
+import Data.Maybe ( fromMaybe )
 import Control.Applicative ((<|>))
 import Control.Monad.State
 import Text.Pandoc.Pretty
@@ -240,7 +241,7 @@ inCmd cmd contents = char '\\' <> text cmd <> braces contents
 toSlides :: [Block] -> State WriterState [Block]
 toSlides bs = do
   opts <- gets stOptions
-  let slideLevel = maybe (getSlideLevel bs) id $ writerSlideLevel opts
+  let slideLevel = fromMaybe (getSlideLevel bs) $ writerSlideLevel opts
   let bs' = prepSlides slideLevel bs
   concat `fmap` (mapM (elementToBeamer slideLevel) $ hierarchicalize bs')
 
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index cc0a06243..25cd5ae13 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -31,6 +31,7 @@ Conversion of 'Pandoc' documents to ODT.
 module Text.Pandoc.Writers.ODT ( writeODT ) where
 import Data.IORef
 import Data.List ( isPrefixOf )
+import Data.Maybe ( fromMaybe )
 import qualified Data.ByteString.Lazy as B
 import Text.Pandoc.UTF8 ( fromStringLazy )
 import Codec.Archive.Zip
@@ -127,7 +128,7 @@ transformPic opts entriesRef (Image lab (src,_)) = do
        return $ Emph lab
      Right (img, _) -> do
        let size = imageSize img
-       let (w,h) = maybe (0,0) id $ sizeInPoints `fmap` size
+       let (w,h) = fromMaybe (0,0) $ sizeInPoints `fmap` size
        let tit' = show w ++ "x" ++ show h
        entries <- readIORef entriesRef
        let newsrc = "Pictures/" ++ show (length entries) ++ takeExtension src