aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2022-10-30 11:02:00 -0700
committerJohn MacFarlane <[email protected]>2022-10-30 11:02:00 -0700
commit8b3be07ae8566f29cbf73062d87c9dd44f99f566 (patch)
treef662aee321bebbdf8d963ec2c24554f729105cfe
parent55b8d0abee2086be12d7dc33f7848f74482ee7e8 (diff)
hlint suggestions.
-rw-r--r--pandoc-cli/no-lua/PandocCLI/Lua.hs1
-rw-r--r--pandoc-cli/src/pandoc.hs1
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua.hs1
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs1
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs3
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Scaffolding.hs2
-rw-r--r--pandoc-lua-engine/test/Tests/Lua/Writer.hs7
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs4
10 files changed, 7 insertions, 17 deletions
diff --git a/pandoc-cli/no-lua/PandocCLI/Lua.hs b/pandoc-cli/no-lua/PandocCLI/Lua.hs
index 350a4cdbc..7ada019e8 100644
--- a/pandoc-cli/no-lua/PandocCLI/Lua.hs
+++ b/pandoc-cli/no-lua/PandocCLI/Lua.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE OverloadedStrings #-}
{- |
Module : PandocCLI.Lua
Copyright : © 2022 Albert Krewinkel
diff --git a/pandoc-cli/src/pandoc.hs b/pandoc-cli/src/pandoc.hs
index 3c0889d8e..8068f6756 100644
--- a/pandoc-cli/src/pandoc.hs
+++ b/pandoc-cli/src/pandoc.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
-{-# LANGUAGE TemplateHaskell #-}
{- |
Module : Main
Copyright : Copyright (C) 2006-2022 John MacFarlane
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua.hs
index d6134fc01..8ff9a7c64 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{- |
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs
index 377ce159b..39b1b98a0 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- |
Module : Text.Pandoc.Lua.Marshaling.Format
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs
index c9721a53d..fe4227c5c 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/PandocError.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Marshal.PandocError
Copyright : © 2020-2022 Albert Krewinkel
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
index 5425a566c..71134c03f 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
@@ -33,7 +33,7 @@ peekTemplate idx = liftLua (ltype idx) >>= \case
let path = "templates/default.custom"
let liftPM = liftLua . unPandocLua
tmpl <- peekText idx
- (liftPM $ runWithDefaultPartials (compileTemplate path tmpl)) >>= \case
+ liftPM (runWithDefaultPartials (compileTemplate path tmpl)) >>= \case
Left e -> failPeek (Lua.fromString e)
Right t -> pure t
_ -> peekUD typeTemplate idx
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs
index 522bdb651..016d453ca 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Classic.hs
@@ -69,7 +69,7 @@ instance Pushable (Stringify MetaValue) where
push (Stringify (MetaBlocks bs)) = Lua.push (Stringify bs)
instance Pushable (Stringify Citation) where
- push (Stringify cit) = flip pushAsTable cit
+ push (Stringify cit) = pushAsTable
[ ("citationId", push . citationId)
, ("citationPrefix", push . Stringify . citationPrefix)
, ("citationSuffix", push . Stringify . citationSuffix)
@@ -77,6 +77,7 @@ instance Pushable (Stringify Citation) where
, ("citationNoteNum", push . citationNoteNum)
, ("citationHash", push . citationHash)
]
+ cit
-- | Key-value pair, pushed as a table with @a@ as the only key and @v@ as the
-- associated value.
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Scaffolding.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Scaffolding.hs
index 6a3fb184e..95ce23c0d 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Scaffolding.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer/Scaffolding.hs
@@ -1,7 +1,5 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE TupleSections #-}
-{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Writer.Scaffolding
Copyright : © 2022 Albert Krewinkel
diff --git a/pandoc-lua-engine/test/Tests/Lua/Writer.hs b/pandoc-lua-engine/test/Tests/Lua/Writer.hs
index 18274d124..c9a0d478c 100644
--- a/pandoc-lua-engine/test/Tests/Lua/Writer.hs
+++ b/pandoc-lua-engine/test/Tests/Lua/Writer.hs
@@ -51,11 +51,10 @@ tests =
, goldenVsString "bytestring writer"
"bytestring.bin"
- (runIOorExplode $ do
- txt <- writeCustom "bytestring.lua" >>= \case
+ (runIOorExplode $
+ writeCustom "bytestring.lua" >>= \case
(ByteStringWriter f, _, _) -> f def mempty
- _ -> error "Expected a bytestring writer"
- pure txt)
+ _ -> error "Expected a bytestring writer")
, goldenVsString "template"
"writer-template.out.txt"
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 58c9e9e2a..32e3e4065 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -830,9 +830,7 @@ options =
(OptArg
(\arg _ -> do
let allExts = getAllExtensions $
- case arg of
- Nothing -> "markdown"
- Just fmt -> T.pack fmt
+ maybe "markdown" T.pack arg
let formatName = maybe "markdown" T.pack arg
if formatName `notElem`
(map fst (readers :: [(Text, Reader PandocPure)]) ++