diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Ipynb.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Man.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TikiWiki.hs | 4 |
6 files changed, 8 insertions, 9 deletions
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 |