aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorIgor Pashev <pashev.igor@gmail.com>2022-01-13 19:11:50 +0200
committerIgor Pashev <pashev.igor@gmail.com>2022-01-16 19:49:37 +0200
commitf62f8b7ef2f1c2357fbd41f5226fe433e632e042 (patch)
tree5b94da2cac9e6a451b21cf183da8311e3b5eb2a1
parentb80b03c0b3d03c9504854fe97e7e6def6fe7c609 (diff)
downloadpandoc-f62f8b7ef2f1c2357fbd41f5226fe433e632e042.tar.gz
LaTeX: parse thebibliographyHEADmaster
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs38
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs2
-rw-r--r--test/command/latex-thebibliography.md49
3 files changed, 89 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 20a2db76b..37fa4adf0 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -741,6 +741,14 @@ looseItem = do
skipopts
return mempty
+looseBibItem :: PandocMonad m => LP m Blocks
+looseBibItem = do
+ inListItem <- sInListItem <$> getState
+ guard $ not inListItem
+ skipopts
+ void braced
+ return mempty
+
epigraph :: PandocMonad m => LP m Blocks
epigraph = do
p1 <- grouped block
@@ -886,6 +894,7 @@ blockCommands = M.fromList
, ("strut", pure mempty)
, ("rule", rule)
, ("item", looseItem)
+ , ("bibitem", looseBibItem)
, ("documentclass", skipopts *> braced *> preamble)
, ("centerline", para . trimInlines <$> (skipopts *> tok))
, ("caption", mempty <$ setCaption inline)
@@ -975,6 +984,7 @@ environments = M.union (tableEnvironments blocks inline) $
, ("togglefalse", braced >>= setToggle False)
, ("iftoggle", try $ ifToggle >> block)
, ("CSLReferences", braced >> braced >> env "CSLReferences" blocks)
+ , ("thebibliography", theBibliography)
]
filecontents :: PandocMonad m => LP m Blocks
@@ -1211,6 +1221,34 @@ descItem = do
bs <- blocks
return (ils, [bs])
+bibItem :: PandocMonad m => LP m (Inlines, [Blocks])
+bibItem = do
+ blocks
+ controlSeq "bibitem"
+ sp
+ lbl <- opt <|> nextNum
+ cite_key <- untokenize <$> braced
+ bs <- blocks
+ return (lbl, [divWith (cite_key, [], []) bs])
+ where
+ nextNum = do
+ st <- getState
+ let n = sTheBibItemNum st + 1
+ setState st {sTheBibItemNum = n}
+ return . str . T.pack . show $ n
+
+theBibliography :: PandocMonad m => LP m Blocks
+theBibliography = do
+ updateState $ \st -> st {sTheBibItemNum = 0}
+ items <- listenv "thebibliography" (many bibItem)
+ is_ol <- (== length items) . sTheBibItemNum <$> getState
+ return $
+ divWith
+ ("", ["thebibliography"], [])
+ (if is_ol
+ then orderedListWith (1, Decimal, Period) $ map (head . snd) items
+ else definitionList items)
+
listenv :: PandocMonad m => Text -> LP m a -> LP m a
listenv name p = try $ do
oldInListItem <- sInListItem `fmap` getState
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index 9eb4a0cbc..8fb6bd5bc 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -172,6 +172,7 @@ data LaTeXState = LaTeXState{ sOptions :: ReaderOptions
, sFileContents :: M.Map Text Text
, sEnableWithRaw :: Bool
, sRawTokens :: IntMap.IntMap [Tok]
+ , sTheBibItemNum :: Int
}
deriving Show
@@ -199,6 +200,7 @@ defaultLaTeXState = LaTeXState{ sOptions = def
, sFileContents = M.empty
, sEnableWithRaw = True
, sRawTokens = IntMap.empty
+ , sTheBibItemNum = 0
}
instance PandocMonad m => HasQuoteContext LaTeXState m where
diff --git a/test/command/latex-thebibliography.md b/test/command/latex-thebibliography.md
new file mode 100644
index 000000000..54b257c61
--- /dev/null
+++ b/test/command/latex-thebibliography.md
@@ -0,0 +1,49 @@
+# The bibliography
+
+```
+% pandoc -f latex -t native
+\begin{thebibliography}{10}
+ \bibitem{two} The Second.
+ \bibitem{four} The Fourth.
+\end{thebibliography}
+\begin{thebibliography}{100}
+ \bibitem[One1990]{one} The First.
+ \bibitem{two} The Second.
+\end{thebibliography}
+^D
+[ Div
+ ( "" , [ "thebibliography" ] , [] )
+ [ OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Div
+ ( "two" , [] , [] )
+ [ Para [ Str "The" , Space , Str "Second." ] ]
+ ]
+ , [ Div
+ ( "four" , [] , [] )
+ [ Para [ Str "The" , Space , Str "Fourth." ] ]
+ ]
+ ]
+ ]
+, Div
+ ( "" , [ "thebibliography" ] , [] )
+ [ DefinitionList
+ [ ( [ Str "One1990" ]
+ , [ [ Div
+ ( "one" , [] , [] )
+ [ Para [ Str "The" , Space , Str "First." ] ]
+ ]
+ ]
+ )
+ , ( [ Str "1" ]
+ , [ [ Div
+ ( "two" , [] , [] )
+ [ Para [ Str "The" , Space , Str "Second." ] ]
+ ]
+ ]
+ )
+ ]
+ ]
+]
+```
+