diff options
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 53 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Parsing.hs | 6 | ||||
-rw-r--r-- | test/command/2118.md | 2 | ||||
-rw-r--r-- | test/command/6137.md | 23 | ||||
-rw-r--r-- | test/command/refs.md | 8 |
5 files changed, 53 insertions, 39 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index cae7a23b7..8046ec798 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1402,10 +1402,18 @@ treatAsInline = Set.fromList , "pagebreak" ] +label :: PandocMonad m => LP m () +label = do + controlSeq "label" + t <- untokenize <$> braced + updateState $ \st -> st{ sLastLabel = Just t } + dolabel :: PandocMonad m => LP m Inlines dolabel = do v <- braced let refstr = untokenize v + updateState $ \st -> + st{ sLastLabel = Just refstr } return $ spanWith (refstr,[],[("label", refstr)]) $ inBrackets $ str $ untokenize v @@ -1682,19 +1690,12 @@ bracketedNum = do Just i -> return i _ -> return 0 -setCaption :: PandocMonad m => LP m Blocks -setCaption = do +setCaption :: PandocMonad m => LP m () +setCaption = try $ do + skipopts ils <- tok - mblabel <- option Nothing $ - try $ spaces >> controlSeq "label" >> (Just <$> tok) - let capt = case mblabel of - Just lab -> let slab = stringify lab - ils' = ils <> spanWith - ("",[],[("label", slab)]) mempty - in (Just ils', Just slab) - Nothing -> (Just ils, Nothing) - updateState $ \st -> st{ sCaption = capt } - return mempty + optional $ try $ spaces *> label + updateState $ \st -> st{ sCaption = Just ils } looseItem :: PandocMonad m => LP m Blocks looseItem = do @@ -1710,7 +1711,8 @@ epigraph = do return $ divWith ("", ["epigraph"], []) (p1 <> p2) resetCaption :: PandocMonad m => LP m () -resetCaption = updateState $ \st -> st{ sCaption = (Nothing, Nothing) } +resetCaption = updateState $ \st -> st{ sCaption = Nothing + , sLastLabel = Nothing } section :: PandocMonad m => Attr -> Int -> LP m Blocks section (ident, classes, kvs) lvl = do @@ -1850,7 +1852,7 @@ blockCommands = M.fromList , ("item", looseItem) , ("documentclass", skipopts *> braced *> preamble) , ("centerline", (para . trimInlines) <$> (skipopts *> tok)) - , ("caption", skipopts *> setCaption) + , ("caption", mempty <$ setCaption) , ("bibliography", mempty <$ (skipopts *> braced >>= addMeta "bibliography" . splitBibs . untokenize)) , ("addbibresource", mempty <$ (skipopts *> braced >>= @@ -1901,7 +1903,7 @@ environments = M.fromList , ("longtable", env "longtable" $ resetCaption *> simpTable "longtable" False >>= addTableCaption) , ("table", env "table" $ - resetCaption *> skipopts *> blocks >>= addTableCaption) + skipopts *> resetCaption *> blocks >>= addTableCaption) , ("tabular*", env "tabular*" $ simpTable "tabular*" True) , ("tabularx", env "tabularx" $ simpTable "tabularx" True) , ("tabular", env "tabular" $ simpTable "tabular" False) @@ -2068,11 +2070,12 @@ 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, mblab) <- sCaption <$> getState + mbcapt <- sCaption <$> getState + mblabel <- sLastLabel <$> getState let (alt', tit') = case mbcapt of Just ils -> (toList ils, "fig:" <> tit) Nothing -> (alt, tit) - attr' = case mblab of + attr' = case mblabel of Just lab -> (lab, cls, kvs) Nothing -> attr case attr' of @@ -2363,7 +2366,10 @@ simpTable envname hasWidthParameter = try $ do colspecs <- parseAligns let (aligns, widths, prefsufs) = unzip3 colspecs let cols = length colspecs - optional $ controlSeq "caption" *> skipopts *> setCaption + optional $ controlSeq "caption" *> setCaption + spaces + optional label + spaces optional lbreak spaces skipMany hline @@ -2374,7 +2380,10 @@ simpTable envname hasWidthParameter = try $ do rows <- sepEndBy (parseTableRow envname prefsufs) (lbreak <* optional (skipMany hline)) spaces - optional $ controlSeq "caption" *> skipopts *> setCaption + optional $ controlSeq "caption" *> setCaption + spaces + optional label + spaces optional lbreak spaces let header'' = if null header' @@ -2386,7 +2395,8 @@ 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, mblabel) <- sCaption <$> getState + mbcapt <- sCaption <$> getState + mblabel <- sLastLabel <$> getState capt <- case (mbcapt, mblabel) of (Just ils, Nothing) -> return $ toList ils (Just ils, Just lab) -> do @@ -2398,7 +2408,8 @@ addTableCaption = walkM go (sLabels st) } return $ toList ils -- add number?? (Nothing, _) -> return c - return $ Table capt als ws hs rs + return $ maybe id (\ident -> Div (ident, [], []) . (:[])) mblabel $ + Table capt als ws hs rs go x = return x diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs index 4aa9976c9..cfd4f1dba 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs @@ -115,12 +115,13 @@ data LaTeXState = LaTeXState{ sOptions :: ReaderOptions , sLogMessages :: [LogMessage] , sIdentifiers :: Set.Set Text , sVerbatimMode :: Bool - , sCaption :: (Maybe Inlines, Maybe Text) + , sCaption :: Maybe Inlines , sInListItem :: Bool , sInTableCell :: Bool , sLastHeaderNum :: DottedNum , sLastFigureNum :: DottedNum , sLastTableNum :: DottedNum + , sLastLabel :: Maybe Text , sLabels :: M.Map Text [Inline] , sHasChapters :: Bool , sToggles :: M.Map Text Bool @@ -137,12 +138,13 @@ defaultLaTeXState = LaTeXState{ sOptions = def , sLogMessages = [] , sIdentifiers = Set.empty , sVerbatimMode = False - , sCaption = (Nothing, Nothing) + , sCaption = Nothing , sInListItem = False , sInTableCell = False , sLastHeaderNum = DottedNum [] , sLastFigureNum = DottedNum [] , sLastTableNum = DottedNum [] + , sLastLabel = Nothing , sLabels = M.empty , sHasChapters = False , sToggles = M.empty diff --git a/test/command/2118.md b/test/command/2118.md index 9730dd383..b38f48c80 100644 --- a/test/command/2118.md +++ b/test/command/2118.md @@ -7,5 +7,5 @@ \label{fig:setminus} \end{figure} ^D -[Para [Image ("fig:setminus",[],[("width","80%")]) [Str "Set",Space,Str "subtraction",Span ("",[],[("label","fig:setminus")]) []] ("setminus.png","fig:")]] +[Para [Image ("fig:setminus",[],[("width","80%")]) [Str "Set",Space,Str "subtraction"] ("setminus.png","fig:")]] ``` diff --git a/test/command/6137.md b/test/command/6137.md index 9c5b71d0c..c1e0ac01c 100644 --- a/test/command/6137.md +++ b/test/command/6137.md @@ -16,16 +16,17 @@ This reference to Figure \ref{fig:label} works fine. \end{figure} ^D [Para [Str "This",Space,Str "reference",Space,Str "to",Space,Str "Table",Space,Link ("",[],[("reference-type","ref"),("reference","tbl:label")]) [Str "1"] ("#tbl:label",""),Space,Str "doesn\8217t",Space,Str "work."] -,Table [Str "This",Space,Str "caption",Space,Str "has",Space,Str "no",Space,Str "number.",Span ("",[],[("label","tbl:label")]) []] [AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0] - [[] - ,[] - ,[]] - [[[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]]] - ,[[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]] - ,[Plain [Str "\8212\8212\8211"]]]] +,Div ("tbl:label",[],[]) + [Table [Str "This",Space,Str "caption",Space,Str "has",Space,Str "no",Space,Str "number."] [AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0] + [[] + ,[] + ,[]] + [[[Plain [Str "\8212\8212\8211"]] + ,[Plain [Str "\8212\8212\8211"]] + ,[Plain [Str "\8212\8212\8211"]]] + ,[[Plain [Str "\8212\8212\8211"]] + ,[Plain [Str "\8212\8212\8211"]] + ,[Plain [Str "\8212\8212\8211"]]]]] ,Para [Str "This",Space,Str "reference",Space,Str "to",Space,Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:label")]) [Str "1"] ("#fig:label",""),Space,Str "works",Space,Str "fine."] -,Para [Image ("fig:label",[],[("width","\\textwidth")]) [Str "A",Space,Str "numbered",Space,Str "caption,",Space,Str "if",Space,Str "I",Space,Str "use",Space,Str "pandoc-crossref.",Span ("",[],[("label","fig:label")]) []] ("example.png","fig:")]] +,Para [Image ("fig:label",[],[("width","\\textwidth")]) [Str "A",Space,Str "numbered",Space,Str "caption,",Space,Str "if",Space,Str "I",Space,Str "use",Space,Str "pandoc-crossref."] ("example.png","fig:")]] ``` diff --git a/test/command/refs.md b/test/command/refs.md index 8b58ea6d7..320d63e17 100644 --- a/test/command/refs.md +++ b/test/command/refs.md @@ -42,7 +42,7 @@ Accuracy~\eqref{eq:Accuracy} is the proportion, measuring true results among all Figure \ref{fig:Logo} illustrated the SVG logo ^D -[Para [Image ("fig:Logo",[],[]) [Str "Logo",Span ("",[],[("label","fig:Logo")]) []] ("command/SVG_logo.svg","fig:")] +[Para [Image ("fig:Logo",[],[]) [Str "Logo"] ("command/SVG_logo.svg","fig:")] ,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo")]) [Str "1"] ("#fig:Logo",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]] ``` @@ -78,11 +78,11 @@ Figure \ref{fig:Logo2} illustrated the SVG logo Figure \ref{fig:Logo3} illustrated the SVG logo ^D [Header 1 ("one",[],[]) [Str "One"] -,Para [Image ("fig:Logo",[],[]) [Str "Logo",Span ("",[],[("label","fig:Logo")]) []] ("command/SVG_logo.svg","fig:")] -,Para [Image ("fig:Logo2",[],[]) [Str "Logo2",Span ("",[],[("label","fig:Logo2")]) []] ("command/SVG_logo2.svg","fig:")] +,Para [Image ("fig:Logo",[],[]) [Str "Logo"] ("command/SVG_logo.svg","fig:")] +,Para [Image ("fig:Logo2",[],[]) [Str "Logo2"] ("command/SVG_logo2.svg","fig:")] ,Header 1 ("two",[],[]) [Str "Two"] ,Header 2 ("subone",[],[]) [Str "Subone"] -,Para [Image ("fig:Logo3",[],[]) [Str "Logo3",Span ("",[],[("label","fig:Logo3")]) []] ("command/SVG_logo3.svg","fig:")] +,Para [Image ("fig:Logo3",[],[]) [Str "Logo3"] ("command/SVG_logo3.svg","fig:")] ,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo")]) [Str "1.1"] ("#fig:Logo",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"] ,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo2")]) [Str "1.2"] ("#fig:Logo2",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"] ,Para [Str "Figure",Space,Link ("",[],[("reference-type","ref"),("reference","fig:Logo3")]) [Str "2.1"] ("#fig:Logo3",""),Space,Str "illustrated",Space,Str "the",Space,Str "SVG",Space,Str "logo"]] |