aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJoseph C. Sible <josephcsible@users.noreply.github.com>2020-02-14 01:52:51 -0500
committerGitHub <noreply@github.com>2020-02-13 22:52:51 -0800
commit652ed0b82cd7095f418859356d7e5f8ada65eb49 (patch)
treebe5df575ea426a839230933a7ac9b3ab7a99c05d /src/Text/Pandoc/Readers
parent29c2670da2a267094148f3edacaed5fc258bcdd1 (diff)
downloadpandoc-652ed0b82cd7095f418859356d7e5f8ada65eb49.tar.gz
A bit more cleanup (#6141)
* Remove unnecessary fmaps and only do toMilliseconds once * Share the input tuple intead of making a new one * Lift return out of if * Simplify case statements * Lift DottedNum out of the case statements * Use st instead of mbs * Use setState instead of updateState now that we have the whole state around
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs9
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs43
2 files changed, 25 insertions, 27 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 057ff1d31..a32e0b829 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -839,11 +839,10 @@ toStringAttr = map go
where
go (x,y) =
case T.stripPrefix "data-" x of
- Nothing -> (x,y)
- Just x' -> if x' `Set.member` (html5Attributes <>
- html4Attributes <> rdfaAttributes)
- then (x,y)
- else (x',y)
+ Just x' | x' `Set.notMember` (html5Attributes <>
+ html4Attributes <> rdfaAttributes)
+ -> (x',y)
+ _ -> (x,y)
pScriptMath :: PandocMonad m => TagParser m Inlines
pScriptMath = try $ do
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 8046ec798..01f3bc527 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1405,8 +1405,8 @@ treatAsInline = Set.fromList
label :: PandocMonad m => LP m ()
label = do
controlSeq "label"
- t <- untokenize <$> braced
- updateState $ \st -> st{ sLastLabel = Just t }
+ t <- braced
+ updateState $ \st -> st{ sLastLabel = Just $ untokenize t }
dolabel :: PandocMonad m => LP m Inlines
dolabel = do
@@ -2070,19 +2070,18 @@ addImageCaption :: PandocMonad m => Blocks -> LP m Blocks
addImageCaption = walkM go
where go (Image attr@(_, cls, kvs) alt (src,tit))
| not ("fig:" `T.isPrefixOf` tit) = do
- mbcapt <- sCaption <$> getState
- mblabel <- sLastLabel <$> getState
- let (alt', tit') = case mbcapt of
+ st <- getState
+ let (alt', tit') = case sCaption st of
Just ils -> (toList ils, "fig:" <> tit)
Nothing -> (alt, tit)
- attr' = case mblabel of
+ attr' = case sLastLabel st of
Just lab -> (lab, cls, kvs)
Nothing -> attr
case attr' of
("", _, _) -> return ()
(ident, _, _) -> do
num <- getNextNumber sLastFigureNum
- updateState $ \st ->
+ setState
st{ sLastFigureNum = num
, sLabels = M.insert ident
[Str (renderDottedNum num)] (sLabels st) }
@@ -2094,25 +2093,25 @@ getNextNumber :: Monad m
getNextNumber getCurrentNum = do
st <- getState
let chapnum =
- case (sHasChapters st, sLastHeaderNum st) of
- (True, DottedNum (n:_)) -> Just n
- _ -> Nothing
- return $
+ case sLastHeaderNum st of
+ DottedNum (n:_) | sHasChapters st -> Just n
+ _ -> Nothing
+ return . DottedNum $
case getCurrentNum st of
DottedNum [m,n] ->
case chapnum of
- Just m' | m' == m -> DottedNum [m, n+1]
- | otherwise -> DottedNum [m', 1]
- Nothing -> DottedNum [1]
+ Just m' | m' == m -> [m, n+1]
+ | otherwise -> [m', 1]
+ Nothing -> [1]
-- shouldn't happen
DottedNum [n] ->
case chapnum of
- Just m -> DottedNum [m, 1]
- Nothing -> DottedNum [n + 1]
+ Just m -> [m, 1]
+ Nothing -> [n + 1]
_ ->
case chapnum of
- Just n -> DottedNum [n, 1]
- Nothing -> DottedNum [1]
+ Just n -> [n, 1]
+ Nothing -> [1]
coloredBlock :: PandocMonad m => Text -> LP m Blocks
@@ -2395,13 +2394,13 @@ simpTable envname hasWidthParameter = try $ do
addTableCaption :: PandocMonad m => Blocks -> LP m Blocks
addTableCaption = walkM go
where go (Table c als ws hs rs) = do
- mbcapt <- sCaption <$> getState
- mblabel <- sLastLabel <$> getState
- capt <- case (mbcapt, mblabel) of
+ st <- getState
+ let mblabel = sLastLabel st
+ capt <- case (sCaption st, mblabel) of
(Just ils, Nothing) -> return $ toList ils
(Just ils, Just lab) -> do
num <- getNextNumber sLastTableNum
- updateState $ \st ->
+ setState
st{ sLastTableNum = num
, sLabels = M.insert lab
[Str (renderDottedNum num)]