LaTeX reader: improve references.

- Resolve references to theorem environments.
- Remove Span caused by "label" in figure, table, and theorem
  environments; this had an id that duplicated the environments' id.

See #813.
This commit is contained in:
John MacFarlane 2021-11-24 18:41:20 -08:00
parent 7726b69cd3
commit 2ca3993c67
4 changed files with 27 additions and 5 deletions

View file

@ -1101,7 +1101,8 @@ addImageCaption = walkM go
case sCaption st of
Nothing -> return p
Just figureCaption -> do
let attr' = case sLastLabel st of
let mblabel = sLastLabel st
let attr' = case mblabel of
Just lab -> (lab, cls, kvs)
Nothing -> attr
case attr' of
@ -1113,7 +1114,9 @@ addImageCaption = walkM go
, sLabels = M.insert ident
[Str (renderDottedNum num)] (sLabels st) }
return $ SimpleFigure attr' (B.toList figureCaption) (src, tit)
return $ SimpleFigure attr'
(maybe id removeLabel mblabel (B.toList figureCaption))
(src, tit)
go x = return x
coloredBlock :: PandocMonad m => Text -> LP m Blocks

View file

@ -142,14 +142,15 @@ newtheorem inline = do
theoremEnvironment :: PandocMonad m
=> LP m Blocks -> LP m Inlines -> Text -> LP m Blocks
theoremEnvironment blocks opt name = do
resetCaption
tmap <- sTheoremMap <$> getState
case M.lookup name tmap of
Nothing -> mzero
Just tspec -> do
optTitle <- option mempty $ (\x -> space <> "(" <> x <> ")") <$> opt
mblabel <- option Nothing $ Just . untokenize <$>
try (spaces >> controlSeq "label" >> spaces >> braced)
bs <- env name blocks
mblabel <- sLastLabel <$> getState
number <-
if theoremNumber tspec
then do
@ -182,6 +183,7 @@ theoremEnvironment blocks opt name = do
let title = titleEmph (theoremName tspec <> number)
<> optTitle <> "." <> space
return $ divWith (fromMaybe "" mblabel, [name], []) $ addTitle title
$ maybe id removeLabel mblabel
$ case theoremStyle tspec of
PlainStyle -> walk italicize bs
_ -> bs

View file

@ -90,6 +90,7 @@ module Text.Pandoc.Readers.LaTeX.Parsing
, resetCaption
, env
, addMeta
, removeLabel
) where
import Control.Applicative (many, (<|>))
@ -119,6 +120,7 @@ import Text.Pandoc.Readers.LaTeX.Types (ExpansionPoint (..), Macro (..),
ArgSpec (..), Tok (..), TokType (..))
import Text.Pandoc.Shared
import Text.Parsec.Pos
import Text.Pandoc.Walk
newtype DottedNum = DottedNum [Int]
deriving (Show, Eq)
@ -1067,3 +1069,16 @@ tokWith inlineParser = try $ spaces >>
addMeta :: PandocMonad m => ToMetaValue a => Text -> a -> LP m ()
addMeta field val = updateState $ \st ->
st{ sMeta = addMetaField field val $ sMeta st }
-- remove label spans to avoid duplicated identifier
removeLabel :: Walkable [Inline] a => Text -> a -> a
removeLabel lbl = walk go
where
go (Span (_,_,kvs) _ : rest)
| Just lbl' <- lookup "label" kvs
, lbl' == lbl = go (dropWhile isSpaceOrSoftBreak rest)
go (x:xs) = x : go xs
go [] = []
isSpaceOrSoftBreak Space = True
isSpaceOrSoftBreak SoftBreak = True
isSpaceOrSoftBreak _ = False

View file

@ -368,7 +368,9 @@ addTableCaption = walkM go
((_,classes,kvs), Just ident) ->
(ident,classes,kvs)
_ -> attr
return $ addAttrDiv attr' $ Table nullAttr capt spec th tb tf
return $ addAttrDiv attr'
$ maybe id removeLabel mblabel
$ Table nullAttr capt spec th tb tf
go x = return x
-- TODO: For now we add a Div to contain table attributes, since