Skip to content

Commit

Permalink
Clean up some fmaps (#6226)
Browse files Browse the repository at this point in the history
* Avoid fmapping when we're just binding right after anyway

* Clean up unnecessary fmaps in the LaTeX reader
  • Loading branch information
josephcsible committed Mar 30, 2020
1 parent 40fd20d commit 377efd0
Show file tree
Hide file tree
Showing 7 changed files with 22 additions and 22 deletions.
2 changes: 1 addition & 1 deletion src/Text/Pandoc/Lua/Module/MediaBag.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ insertMediaFn fp optionalMime contents = do

-- | Returns iterator values to be used with a Lua @for@ loop.
items :: Lua NumResults
items = stMediaBag <$> getCommonState >>= pushIterator
items = getCommonState >>= pushIterator . stMediaBag

lookupMediaFn :: FilePath
-> Lua NumResults
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Readers/DocBook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -758,8 +758,8 @@ parseBlock (Elem e) =
"upperroman" -> UpperRoman
_ -> Decimal
let start = fromMaybe 1 $
(attrValue "override" <$> filterElement (named "listitem") e)
>>= safeRead
filterElement (named "listitem") e
>>= safeRead . attrValue "override"
orderedListWith (start,listStyle,DefaultDelim)
<$> listitems
"variablelist" -> definitionList <$> deflistitems
Expand Down
6 changes: 3 additions & 3 deletions src/Text/Pandoc/Readers/JATS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,9 +164,9 @@ parseBlock (Elem e) =
"bullet" -> bulletList <$> listitems
listType -> do
let start = fromMaybe 1 $
(textContent <$> (filterElement (named "list-item") e
>>= filterElement (named "label")))
>>= safeRead
(filterElement (named "list-item") e
>>= filterElement (named "label"))
>>= safeRead . textContent
orderedListWith (start, parseListStyleType listType, DefaultDelim)
<$> listitems
"def-list" -> definitionList <$> deflistitems
Expand Down
18 changes: 9 additions & 9 deletions src/Text/Pandoc/Readers/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1018,16 +1018,16 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
, ("lstinline", dolstinline)
, ("mintinline", domintinline)
, ("Verb", doverb)
, ("url", ((unescapeURL . untokenize) <$> bracedUrl) >>= \url ->
pure (link url "" (str url)))
, ("nolinkurl", ((unescapeURL . untokenize) <$> bracedUrl) >>= \url ->
pure (code url))
, ("href", (unescapeURL . untokenize <$>
bracedUrl <* sp) >>= \url ->
tok >>= \lab -> pure (link url "" lab))
, ("url", (\url -> link url "" (str url)) . unescapeURL . untokenize <$>
bracedUrl)
, ("nolinkurl", code . unescapeURL . untokenize <$> bracedUrl)
, ("href", do url <- bracedUrl
sp
link (unescapeURL $ untokenize url) "" <$> tok)
, ("includegraphics", do options <- option [] keyvals
src <- unescapeURL . removeDoubleQuotes . untokenize <$> braced
mkImage options src)
src <- braced
mkImage options . unescapeURL . removeDoubleQuotes $
untokenize src)
, ("enquote*", enquote True Nothing)
, ("enquote", enquote False Nothing)
-- foreignquote is supposed to use native quote marks
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Readers/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1339,8 +1339,8 @@ pipeTableRow = try $ do
-- split into cells
let chunk = void (code <|> math <|> rawHtmlInline <|> escapedChar <|> rawLaTeXInline')
<|> void (noneOf "|\n\r")
let cellContents = ((trim . snd) <$> withRaw (many chunk)) >>=
parseFromString' pipeTableCell
let cellContents = withRaw (many chunk) >>=
parseFromString' pipeTableCell . trim . snd
cells <- cellContents `sepEndBy1` char '|'
-- surrounding pipes needed for a one-column table:
guard $ not (length cells == 1 && not openPipe)
Expand Down
6 changes: 3 additions & 3 deletions src/Text/Pandoc/Writers/Docx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -236,11 +236,11 @@ writeDocx opts doc@(Pandoc meta _) = do

-- Gets the template size
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 mbAttrMarLeft = (elAttribs <$> mbpgmar) >>= lookupAttrTextBy ((=="left") . qName)
let mbAttrMarRight = (elAttribs <$> mbpgmar) >>= lookupAttrTextBy ((=="right") . qName)
let mbAttrMarLeft = mbpgmar >>= lookupAttrTextBy ((=="left") . qName) . elAttribs
let mbAttrMarRight = mbpgmar >>= lookupAttrTextBy ((=="right") . qName) . elAttribs

-- Get the available area (converting the size and the margins to int and
-- doing the difference
Expand Down
4 changes: 2 additions & 2 deletions src/Text/Pandoc/Writers/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -360,9 +360,9 @@ beginsWithOrderedListMarker str =

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

Expand Down

0 comments on commit 377efd0

Please sign in to comment.