Fixed compiler warnings.

This commit is contained in:
John MacFarlane 2016-07-14 23:38:44 -07:00
parent c203ace130
commit 2f54de7cc4
6 changed files with 11 additions and 14 deletions

View file

@ -865,7 +865,7 @@ gridTableFooter = blanklines
---
-- | Removes the ParsecT layer from the monad transformer stack
readWithM :: (Monad m, Functor m)
readWithM :: (Monad m)
=> ParserT [Char] st m a -- ^ parser
-> st -- ^ initial state
-> String -- ^ input
@ -891,7 +891,7 @@ readWithWarnings p = readWith $ do
return (doc, warnings)
-- | Parse a string with @parser@ (for testing).
testStringWith :: (Show a, Stream [Char] Identity Char)
testStringWith :: (Show a)
=> ParserT [Char] ParserState Identity a
-> [Char]
-> IO ()
@ -1267,7 +1267,7 @@ addWarning mbpos msg =
stateWarnings = (msg ++ maybe "" (\pos -> " " ++ show pos) mbpos) :
stateWarnings st }
infixr 5 <+?>
(<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a
(<+?>) :: (Monoid a) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a
a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>)
extractIdClass :: Attr -> Attr

View file

@ -208,8 +208,7 @@ chomp d = Doc (fromList dl')
go (Prefixed s d' : xs) = Prefixed s (chomp d') : xs
go xs = xs
outp :: (IsString a, Monoid a)
=> Int -> String -> DocState a
outp :: (IsString a) => Int -> String -> DocState a
outp off s | off < 0 = do -- offset < 0 means newline characters
st' <- get
let rawpref = prefix st'
@ -234,8 +233,7 @@ outp off s = do -- offset >= 0 (0 might be combining char)
-- | Renders a 'Doc'. @render (Just n)@ will use
-- a line length of @n@ to reflow text on breakable spaces.
-- @render Nothing@ will not reflow text.
render :: (Monoid a, IsString a)
=> Maybe Int -> Doc -> a
render :: (IsString a) => Maybe Int -> Doc -> a
render linelen doc = fromString . mconcat . reverse . output $
execState (renderDoc doc) startingState
where startingState = RenderState{

View file

@ -205,7 +205,7 @@ orderedList :: String -> TWParser B.Blocks
orderedList prefix = tryMsg "orderedList" $
parseList prefix (oneOf "1iIaA") (string ". ")
parseList :: Show a => String -> TWParser Char -> TWParser a -> TWParser B.Blocks
parseList :: String -> TWParser Char -> TWParser a -> TWParser B.Blocks
parseList prefix marker delim = do
(indent, style) <- lookAhead $ string prefix *> listStyle <* delim
blocks <- many $ parseListItem (prefix ++ indent) (char style <* delim)
@ -281,7 +281,7 @@ tableParseColumn = char '|' *> skipSpaces *>
tableEndOfRow :: TWParser Char
tableEndOfRow = lookAhead (try $ char '|' >> char '\n') >> char '|'
tableColumnContent :: Show a => TWParser a -> TWParser B.Blocks
tableColumnContent :: TWParser a -> TWParser B.Blocks
tableColumnContent end = manyTill content (lookAhead $ try end) >>= return . B.plain . mconcat
where
content = continuation <|> inline
@ -351,11 +351,11 @@ linebreak = newline >> notFollowedBy newline >> (lastNewline <|> innerNewline)
where lastNewline = eof >> return mempty
innerNewline = return B.space
between :: (Show b, Monoid c) => TWParser a -> TWParser b -> (TWParser b -> TWParser c) -> TWParser c
between :: (Monoid c) => TWParser a -> TWParser b -> (TWParser b -> TWParser c) -> TWParser c
between start end p =
mconcat <$> try (start >> notFollowedBy whitespace >> many1Till (p end) end)
enclosed :: (Show a, Monoid b) => TWParser a -> (TWParser a -> TWParser b) -> TWParser b
enclosed :: (Monoid b) => TWParser a -> (TWParser a -> TWParser b) -> TWParser b
enclosed sep p = between sep (try $ sep <* endMarker) p
where
endMarker = lookAhead $ skip endSpace <|> skip (oneOf ".,!?:)|") <|> eof

View file

@ -285,7 +285,7 @@ table = try $ do
(zip aligns (replicate ncolumns 0.0))
headerPadded rowsPadded
pad :: (Show a, Monoid a) => Int -> [a] -> [a]
pad :: (Monoid a) => Int -> [a] -> [a]
pad n xs = xs ++ (replicate (n - length xs) mempty)

View file

@ -38,7 +38,6 @@ import qualified Data.Set as Set
import qualified Text.Pandoc.UTF8 as UTF8
import Codec.Archive.Zip
import Data.Time.Clock.POSIX
import Data.Time.Clock
import System.Environment
import Text.Pandoc.Compat.Time
import Text.Pandoc.Definition

View file

@ -888,7 +888,7 @@ transformInline opts mediaRef (RawInline fmt raw)
return $ RawInline fmt (renderTags' tags')
transformInline _ _ x = return x
(!) :: Node t => (t -> Element) -> [(String, String)] -> t -> Element
(!) :: (t -> Element) -> [(String, String)] -> t -> Element
(!) f attrs n = add_attrs (map (\(k,v) -> Attr (unqual k) v) attrs) (f n)
-- | Version of 'ppTopElement' that specifies UTF-8 encoding.