aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorPete Ryland <pdr@pdr.cx>2019-07-02 10:29:34 +0200
committerJohn MacFarlane <jgm@berkeley.edu>2019-07-02 10:29:34 +0200
commit24c781039fb280604eb1a73dd7de154db9e1e236 (patch)
tree4159323a476918f8eafca3048fadfcfe789d498f /src/Text/Pandoc
parentb6c53553a929a8623ce56af961d28d5dcc4750d5 (diff)
downloadpandoc-24c781039fb280604eb1a73dd7de154db9e1e236.tar.gz
Fix redundant constraint warnings. (#5625)
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Lua/Filter.hs2
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs14
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Readers/Ipynb.hs2
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Readers/Man.hs3
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs2
-rw-r--r--src/Text/Pandoc/Readers/TikiWiki.hs4
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs6
10 files changed, 19 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs
index 553dda8de..e8958347d 100644
--- a/src/Text/Pandoc/Lua/Filter.hs
+++ b/src/Text/Pandoc/Lua/Filter.hs
@@ -129,7 +129,7 @@ walkMWithLuaFilter :: LuaFilter -> Pandoc -> Lua Pandoc
walkMWithLuaFilter f =
walkInlines f >=> walkBlocks f >=> walkMeta f >=> walkPandoc f
-mconcatMapM :: (Monad m, Functor m) => (a -> m [a]) -> [a] -> m [a]
+mconcatMapM :: (Monad m) => (a -> m [a]) -> [a] -> m [a]
mconcatMapM f = fmap mconcat . mapM f
hasOneOf :: LuaFilter -> [String] -> Bool
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 8f7653550..09892db49 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -46,7 +46,7 @@ pushModule datadir = do
LuaUtil.addFunction "walk_inline" walkInline
return 1
-walkElement :: (Pushable a, Walkable [Inline] a, Walkable [Block] a)
+walkElement :: (Walkable [Inline] a, Walkable [Block] a)
=> a -> LuaFilter -> Lua a
walkElement x f = walkInlines f x >>= walkBlocks f
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 15349314f..49249bec8 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -313,8 +313,7 @@ many1Till p end = do
return (first:rest)
-- | Like @manyTill@, but also returns the result of end parser.
-manyUntil :: (Stream s m t)
- => ParserT s u m a
+manyUntil :: ParserT s u m a
-> ParserT s u m b
-> ParserT s u m ([a], b)
manyUntil p end = scan
@@ -328,8 +327,7 @@ manyUntil p end = scan
-- | Like @sepBy1@ from Parsec,
-- but does not fail if it @sep@ succeeds and @p@ fails.
-sepBy1' :: (Stream s m t)
- => ParsecT s u m a
+sepBy1' :: ParsecT s u m a
-> ParsecT s u m sep
-> ParsecT s u m [a]
sepBy1' p sep = (:) <$> p <*> many (try $ sep >> p)
@@ -440,7 +438,7 @@ stringAnyCase (x:xs) = do
return (firstChar:rest)
-- | Parse contents of 'str' using 'parser' and return result.
-parseFromString :: (Monad m, Stream s m Char, IsString s)
+parseFromString :: (Stream s m Char, IsString s)
=> ParserT s st m r
-> String
-> ParserT s st m r
@@ -458,7 +456,7 @@ parseFromString parser str = do
-- | Like 'parseFromString' but specialized for 'ParserState'.
-- This resets 'stateLastStrPos', which is almost always what we want.
-parseFromString' :: (Monad m, Stream s m Char, IsString s)
+parseFromString' :: (Stream s m Char, IsString s)
=> ParserT s ParserState m a
-> String
-> ParserT s ParserState m a
@@ -1019,7 +1017,7 @@ gridTableFooter = blanklines
---
-- | Removes the ParsecT layer from the monad transformer stack
-readWithM :: (Monad m, Stream s m Char, ToString s)
+readWithM :: (Stream s m Char, ToString s)
=> ParserT s st m a -- ^ parser
-> st -- ^ initial state
-> s -- ^ input
@@ -1410,7 +1408,7 @@ extractIdClass (ident, cls, kvs) = (ident', cls', kvs')
Nothing -> cls
kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs
-insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st, Monad mf)
+insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st)
=> ParserT [a] st m (mf Blocks)
-> (String -> [a])
-> [FilePath] -> FilePath
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 78b377993..392530609 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -435,7 +435,7 @@ eSection = try $ do
TagOpen tag _ <- lookAhead $ pSatisfy sectTag
setInChapter (pInTags tag block)
-headerLevel :: PandocMonad m => Text -> TagParser m Int
+headerLevel :: Text -> TagParser m Int
headerLevel tagtype =
case safeRead (T.unpack (T.drop 1 tagtype)) of
Just level ->
@@ -1129,7 +1129,7 @@ _ `closes` _ = False
--- parsers for use in markdown, textile readers
-- | Matches a stretch of HTML in balanced tags.
-htmlInBalanced :: (HasReaderOptions st, Monad m)
+htmlInBalanced :: Monad m
=> (Tag String -> Bool)
-> ParserT String st m String
htmlInBalanced f = try $ do
diff --git a/src/Text/Pandoc/Readers/Ipynb.hs b/src/Text/Pandoc/Readers/Ipynb.hs
index 04e0b1595..dbca5a59f 100644
--- a/src/Text/Pandoc/Readers/Ipynb.hs
+++ b/src/Text/Pandoc/Readers/Ipynb.hs
@@ -53,7 +53,7 @@ readIpynb opts t = do
Right (notebook3 :: Notebook NbV3) -> notebookToPandoc opts notebook3
Left err -> throwError $ PandocIpynbDecodingError err
-notebookToPandoc :: (PandocMonad m, FromJSON (Notebook a))
+notebookToPandoc :: PandocMonad m
=> ReaderOptions -> Notebook a -> m Pandoc
notebookToPandoc opts notebook = do
let cells = notebookCells notebook
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 15c5abf46..09638e5ed 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1379,7 +1379,7 @@ doref cls = do
""
(inBrackets $ str refstr)
-lookupListDefault :: (Show k, Ord k) => v -> [k] -> M.Map k v -> v
+lookupListDefault :: (Ord k) => v -> [k] -> M.Map k v -> v
lookupListDefault d = (fromMaybe d .) . lookupList
where lookupList l m = msum $ map (`M.lookup` m) l
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index a9676c960..c21fd00c3 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -323,8 +323,7 @@ parseItalic [] = do
parseItalic args = return $
emph $ mconcat $ intersperse B.space $ map linePartsToInlines args
-parseAlternatingFonts :: PandocMonad m
- => [Inlines -> Inlines]
+parseAlternatingFonts :: [Inlines -> Inlines]
-> [Arg]
-> ManParser m Inlines
parseAlternatingFonts constructors args = return $ mconcat $
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 9c409510f..46ddc4257 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -772,7 +772,7 @@ bulletList = try $ do
fmap (B.bulletList . compactify) . sequence
<$> many1 (listItem (bulletListStart `indented` indent))
-indented :: Monad m => OrgParser m Int -> Int -> OrgParser m Int
+indented :: OrgParser m Int -> Int -> OrgParser m Int
indented indentedMarker minIndent = try $ do
n <- indentedMarker
guard (minIndent <= n)
diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs
index 8e01a80f8..5daf6b0bb 100644
--- a/src/Text/Pandoc/Readers/TikiWiki.hs
+++ b/src/Text/Pandoc/Readers/TikiWiki.hs
@@ -54,10 +54,10 @@ type TikiWikiParser = ParserT [Char] ParserState
-- utility functions
--
-tryMsg :: PandocMonad m => String -> TikiWikiParser m a -> TikiWikiParser m a
+tryMsg :: String -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg msg p = try p <?> msg
-skip :: PandocMonad m => TikiWikiParser m a -> TikiWikiParser m ()
+skip :: TikiWikiParser m a -> TikiWikiParser m ()
skip parser = Control.Monad.void parser
nested :: PandocMonad m => TikiWikiParser m a -> TikiWikiParser m a
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index 1f55be797..a9163b3b9 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -63,7 +63,7 @@ import Text.Pandoc.XML (escapeStringForXML)
-- Variables overwrite metadata fields with the same names.
-- If multiple variables are set with the same name, a list is
-- assigned. Does nothing if 'writerTemplate' is Nothing.
-metaToJSON :: (Functor m, Monad m, ToJSON a)
+metaToJSON :: (Monad m, ToJSON a)
=> WriterOptions
-> ([Block] -> m a)
-> ([Inline] -> m a)
@@ -76,7 +76,7 @@ metaToJSON opts blockWriter inlineWriter meta
-- | Like 'metaToJSON', but does not include variables and is
-- not sensitive to 'writerTemplate'.
-metaToJSON' :: (Functor m, Monad m, ToJSON a)
+metaToJSON' :: (Monad m, ToJSON a)
=> ([Block] -> m a)
-> ([Inline] -> m a)
-> Meta
@@ -99,7 +99,7 @@ addVariablesToJSON opts metadata =
where combineMetadata (Object o1) (Object o2) = Object $ H.union o1 o2
combineMetadata x _ = x
-metaValueToJSON :: (Functor m, Monad m, ToJSON a)
+metaValueToJSON :: (Monad m, ToJSON a)
=> ([Block] -> m a)
-> ([Inline] -> m a)
-> MetaValue