aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2022-10-30 12:36:48 -0700
committerJohn MacFarlane <[email protected]>2022-10-30 12:37:19 -0700
commitc7af10fe8957f544407397a56a0c0724b41845d1 (patch)
treef641085c8a404eeeeae9147304d59edb9a381ef0
parent8b3be07ae8566f29cbf73062d87c9dd44f99f566 (diff)
hlint suggestions.
-rw-r--r--Makefile3
-rw-r--r--src/Text/Pandoc/Extensions.hs1
-rw-r--r--src/Text/Pandoc/Parsing/General.hs2
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs4
-rw-r--r--src/Text/Pandoc/Writers/Man.hs2
-rw-r--r--src/Text/Pandoc/Writers/RST.hs2
6 files changed, 7 insertions, 7 deletions
diff --git a/Makefile b/Makefile
index 8108adc83..f73791a6c 100644
--- a/Makefile
+++ b/Makefile
@@ -107,7 +107,8 @@ reformat: ## reformat with stylish-haskell
.PHONY: reformat
lint: ## run hlint
- for f in $(SOURCEFILES); do echo $$f; hlint $$f; done
+ hlint --report=hlint.html $(SOURCEFILES)
+ open hlint.html
.PHONY: lint
fix_spacing: ## fix trailing newlines and spaces
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index a23659b2a..1751295ad 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Extensions
diff --git a/src/Text/Pandoc/Parsing/General.hs b/src/Text/Pandoc/Parsing/General.hs
index 0f9057d44..de099c33b 100644
--- a/src/Text/Pandoc/Parsing/General.hs
+++ b/src/Text/Pandoc/Parsing/General.hs
@@ -100,6 +100,7 @@ import Text.Pandoc.Sources
import Text.Pandoc.XML (fromEntities, lookupEntity)
import Text.Parsec
( (<|>)
+ , Parsec
, ParsecT
, SourcePos
, sourceLine
@@ -132,7 +133,6 @@ import Text.Parsec
, updateState
)
import Text.Parsec.Pos (initialPos, newPos)
-import Text.Parsec (Parsec)
import Text.Pandoc.Error
( PandocError(PandocParseError) )
import Text.Pandoc.Parsing.Capabilities
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 9e909bed6..1c61dd2d0 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -310,9 +310,9 @@ tableToConTeXt (Ann.Table attr caption colspecs thead tbodies tfoot) = do
]
setupCols :: [ColSpec] -> Doc Text
-setupCols = vcat . map toColSetup . zip [1::Int ..]
+setupCols = vcat . zipWith toColSetup [1::Int ..]
where
- toColSetup (i, (align, width)) =
+ toColSetup i (align, width) =
let opts = filter (not . isEmpty)
[ case align of
AlignLeft -> "align=right"
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index f4d829059..ba40cf7c5 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -74,7 +74,7 @@ pandocToMan opts (Pandoc meta blocks) = do
$ setFieldsFromTitle
$ defField "has-tables" hasTables
$ defField "hyphenate" True
- $ metadata
+ metadata
return $ render colwidth $
case writerTemplate opts of
Nothing -> main
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index d783852cd..023f1b4f1 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -205,7 +205,7 @@ escapeText opts t =
'.':'.':'.':ds
| isSmart
-> '\\' : '.' : escapeString' False ('.':'.':ds)
- e:[]
+ [e]
| e == '*' || e == '_' || e == '|' || e == '`'
-> ['\\',e]
d:ds