Clean up some fmaps (#6226)

* Avoid fmapping when we're just binding right after anyway

* Clean up unnecessary fmaps in the LaTeX reader
This commit is contained in:
Joseph C. Sible 2020-03-30 00:11:05 -04:00 committed by GitHub
parent 40fd20d43f
commit 377efd0ce7
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
7 changed files with 22 additions and 22 deletions

View file

@ -85,7 +85,7 @@ insertMediaFn fp optionalMime contents = do
-- | Returns iterator values to be used with a Lua @for@ loop. -- | Returns iterator values to be used with a Lua @for@ loop.
items :: Lua NumResults items :: Lua NumResults
items = stMediaBag <$> getCommonState >>= pushIterator items = getCommonState >>= pushIterator . stMediaBag
lookupMediaFn :: FilePath lookupMediaFn :: FilePath
-> Lua NumResults -> Lua NumResults

View file

@ -758,8 +758,8 @@ parseBlock (Elem e) =
"upperroman" -> UpperRoman "upperroman" -> UpperRoman
_ -> Decimal _ -> Decimal
let start = fromMaybe 1 $ let start = fromMaybe 1 $
(attrValue "override" <$> filterElement (named "listitem") e) filterElement (named "listitem") e
>>= safeRead >>= safeRead . attrValue "override"
orderedListWith (start,listStyle,DefaultDelim) orderedListWith (start,listStyle,DefaultDelim)
<$> listitems <$> listitems
"variablelist" -> definitionList <$> deflistitems "variablelist" -> definitionList <$> deflistitems

View file

@ -164,9 +164,9 @@ parseBlock (Elem e) =
"bullet" -> bulletList <$> listitems "bullet" -> bulletList <$> listitems
listType -> do listType -> do
let start = fromMaybe 1 $ let start = fromMaybe 1 $
(textContent <$> (filterElement (named "list-item") e (filterElement (named "list-item") e
>>= filterElement (named "label"))) >>= filterElement (named "label"))
>>= safeRead >>= safeRead . textContent
orderedListWith (start, parseListStyleType listType, DefaultDelim) orderedListWith (start, parseListStyleType listType, DefaultDelim)
<$> listitems <$> listitems
"def-list" -> definitionList <$> deflistitems "def-list" -> definitionList <$> deflistitems

View file

@ -1018,16 +1018,16 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
, ("lstinline", dolstinline) , ("lstinline", dolstinline)
, ("mintinline", domintinline) , ("mintinline", domintinline)
, ("Verb", doverb) , ("Verb", doverb)
, ("url", ((unescapeURL . untokenize) <$> bracedUrl) >>= \url -> , ("url", (\url -> link url "" (str url)) . unescapeURL . untokenize <$>
pure (link url "" (str url))) bracedUrl)
, ("nolinkurl", ((unescapeURL . untokenize) <$> bracedUrl) >>= \url -> , ("nolinkurl", code . unescapeURL . untokenize <$> bracedUrl)
pure (code url)) , ("href", do url <- bracedUrl
, ("href", (unescapeURL . untokenize <$> sp
bracedUrl <* sp) >>= \url -> link (unescapeURL $ untokenize url) "" <$> tok)
tok >>= \lab -> pure (link url "" lab))
, ("includegraphics", do options <- option [] keyvals , ("includegraphics", do options <- option [] keyvals
src <- unescapeURL . removeDoubleQuotes . untokenize <$> braced src <- braced
mkImage options src) mkImage options . unescapeURL . removeDoubleQuotes $
untokenize src)
, ("enquote*", enquote True Nothing) , ("enquote*", enquote True Nothing)
, ("enquote", enquote False Nothing) , ("enquote", enquote False Nothing)
-- foreignquote is supposed to use native quote marks -- foreignquote is supposed to use native quote marks

View file

@ -1339,8 +1339,8 @@ pipeTableRow = try $ do
-- split into cells -- split into cells
let chunk = void (code <|> math <|> rawHtmlInline <|> escapedChar <|> rawLaTeXInline') let chunk = void (code <|> math <|> rawHtmlInline <|> escapedChar <|> rawLaTeXInline')
<|> void (noneOf "|\n\r") <|> void (noneOf "|\n\r")
let cellContents = ((trim . snd) <$> withRaw (many chunk)) >>= let cellContents = withRaw (many chunk) >>=
parseFromString' pipeTableCell parseFromString' pipeTableCell . trim . snd
cells <- cellContents `sepEndBy1` char '|' cells <- cellContents `sepEndBy1` char '|'
-- surrounding pipes needed for a one-column table: -- surrounding pipes needed for a one-column table:
guard $ not (length cells == 1 && not openPipe) guard $ not (length cells == 1 && not openPipe)

View file

@ -236,11 +236,11 @@ writeDocx opts doc@(Pandoc meta _) = do
-- Gets the template size -- Gets the template size
let mbpgsz = mbsectpr >>= filterElementName (wname (=="pgSz")) let mbpgsz = mbsectpr >>= filterElementName (wname (=="pgSz"))
let mbAttrSzWidth = (elAttribs <$> mbpgsz) >>= lookupAttrTextBy ((=="w") . qName) let mbAttrSzWidth = mbpgsz >>= lookupAttrTextBy ((=="w") . qName) . elAttribs
let mbpgmar = mbsectpr >>= filterElementName (wname (=="pgMar")) let mbpgmar = mbsectpr >>= filterElementName (wname (=="pgMar"))
let mbAttrMarLeft = (elAttribs <$> mbpgmar) >>= lookupAttrTextBy ((=="left") . qName) let mbAttrMarLeft = mbpgmar >>= lookupAttrTextBy ((=="left") . qName) . elAttribs
let mbAttrMarRight = (elAttribs <$> mbpgmar) >>= lookupAttrTextBy ((=="right") . qName) let mbAttrMarRight = mbpgmar >>= lookupAttrTextBy ((=="right") . qName) . elAttribs
-- Get the available area (converting the size and the margins to int and -- Get the available area (converting the size and the margins to int and
-- doing the difference -- doing the difference

View file

@ -360,9 +360,9 @@ beginsWithOrderedListMarker str =
notesAndRefs :: PandocMonad m => WriterOptions -> MD m (Doc Text) notesAndRefs :: PandocMonad m => WriterOptions -> MD m (Doc Text)
notesAndRefs opts = do notesAndRefs opts = do
notes' <- reverse <$> gets stNotes >>= notesToMarkdown opts notes' <- gets stNotes >>= notesToMarkdown opts . reverse
modify $ \s -> s { stNotes = [] } modify $ \s -> s { stNotes = [] }
refs' <- reverse <$> gets stRefs >>= refsToMarkdown opts refs' <- gets stRefs >>= refsToMarkdown opts . reverse
modify $ \s -> s { stPrevRefs = stPrevRefs s ++ stRefs s modify $ \s -> s { stPrevRefs = stPrevRefs s ++ stRefs s
, stRefs = []} , stRefs = []}