diff --git a/src/Text/Pandoc/Filter.hs b/src/Text/Pandoc/Filter.hs
index 84015ed92..cea65bb21 100644
--- a/src/Text/Pandoc/Filter.hs
+++ b/src/Text/Pandoc/Filter.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP               #-}
 {-# LANGUAGE DeriveGeneric     #-}
-{-# LANGUAGE TemplateHaskell   #-}
 {-# LANGUAGE OverloadedStrings #-}
 {- |
    Module      : Text.Pandoc.Filter
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index 2268f29f7..cd02599c9 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric      #-}
-{-# LANGUAGE LambdaCase         #-}
 {-# LANGUAGE OverloadedStrings  #-}
 {- |
    Module      : Text.Pandoc.Logging
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index be90eb23e..e19ad6e67 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -1007,13 +1007,12 @@ parseBlock (Elem e) =
            b <- getBlocks e
            modify $ \st -> st{ dbSectionLevel = n - 1 }
            return $ headerWith (elId, classes, maybeToList titleabbrevElAsAttr++attrs) n' headerText <> b
-         titleabbrevElAsAttr = do
-           txt <- case filterChild (named "titleabbrev") e `mplus`
-                            (filterChild (named "info") e >>=
-                                filterChild (named "titleabbrev")) of
-                            Just t  -> Just ("titleabbrev", strContentRecursive t)
-                            Nothing -> Nothing
-           return txt
+         titleabbrevElAsAttr =
+           case filterChild (named "titleabbrev") e `mplus`
+                (filterChild (named "info") e >>=
+                 filterChild (named "titleabbrev")) of
+             Just t  -> Just ("titleabbrev", strContentRecursive t)
+             Nothing -> Nothing
          lineItems = mapM getInlines $ filterChildren (named "line") e
          -- | Admonitions are parsed into a div. Following other Docbook tools that output HTML,
          -- we parse the optional title as a div with the @title@ class, and give the
diff --git a/src/Text/Pandoc/Writers/Blaze.hs b/src/Text/Pandoc/Writers/Blaze.hs
index 0e3bd0f98..4bd21b789 100644
--- a/src/Text/Pandoc/Writers/Blaze.hs
+++ b/src/Text/Pandoc/Writers/Blaze.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {- |
-   Module      : Text.Pandoc.Writers.Shared
-   Copyright   : Copyright (C) 2021 John MacFarlane
+   Module      : Text.Pandoc.Writers.Blaze
+   Copyright   : Copyright (C) 2021-2022 John MacFarlane
    License     : GNU GPL, version 2 or above
 
    Maintainer  : John MacFarlane <jgm@berkeley.edu>
@@ -112,12 +112,10 @@ withWrap wrap
 toChunks :: Text -> [Doc Text]
 toChunks = map toDoc . T.groupBy sameStatus
   where
-   toDoc t =
-     if T.any (== ' ') t
-        then space
-        else if T.any (== '\n') t
-                then cr
-                else literal t
+   toDoc t
+     | T.any (== ' ')  t = space
+     | T.any (== '\n') t = cr
+     | otherwise         = literal t
    sameStatus c d =
      (c == ' ' && d == ' ') ||
      (c == '\n' && d == '\n') ||