aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/LaTeX.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX.hs')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs38
1 files changed, 38 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