aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs25
-rw-r--r--test/command/6030.md43
2 files changed, 60 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index f845d7444..c1d4fdae1 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -53,7 +53,7 @@ data WriterState =
, stInQuote :: Bool -- true if in a blockquote
, stExternalNotes :: Bool -- true if in context where
-- we need to store footnotes
- , stInMinipage :: Bool -- true if in minipage
+ , stInMinipage :: Bool -- true if in minipage
, stInHeading :: Bool -- true if in a section heading
, stInItem :: Bool -- true if in \item[..]
, stNotes :: [Doc Text] -- notes in a minipage
@@ -455,11 +455,21 @@ toSlides bs = do
-- this creates section slides and marks slides with class "slide","block"
elementToBeamer :: PandocMonad m => Int -> Block -> LW m Block
-elementToBeamer slideLevel d@(Div (ident,dclasses,dkvs)
- xs@(Header lvl _ _ : _))
- | lvl > slideLevel = return $ Div (ident,"block":dclasses,dkvs) xs
- | lvl < slideLevel = return d
- | otherwise = return $ Div (ident,"slide":dclasses,dkvs) xs
+elementToBeamer slideLevel (Div (ident,"section":dclasses,dkvs)
+ xs@(h@(Header lvl _ _) : ys))
+ | lvl > slideLevel
+ = return $ Div (ident,"block":dclasses,dkvs) xs
+ | lvl < slideLevel
+ = do let isDiv (Div{}) = True
+ isDiv _ = False
+ let (titleBs, slideBs) = break isDiv ys
+ return $
+ if null titleBs
+ then Div (ident,dclasses,dkvs) xs
+ else Div (ident,dclasses,dkvs)
+ (h : Div ("","slide":dclasses,dkvs) (h:titleBs) : slideBs)
+ | otherwise
+ = return $ Div (ident,"slide":dclasses,dkvs) xs
elementToBeamer _ x = return x
isListBlock :: Block -> Bool
@@ -516,8 +526,7 @@ blockToLaTeX (Div (identifier,"slide":dclasses,dkvs)
braces (literal ref) <> braces empty
contents <- blockListToLaTeX bs >>= wrapDiv (identifier,classes,kvs)
return $ ("\\begin{frame}" <> options <> slideTitle <> slideAnchor) $$
- contents $$
- "\\end{frame}"
+ contents $$ "\\end{frame}"
blockToLaTeX (Div (identifier@(T.uncons -> Just (_,_)),dclasses,dkvs)
(Header lvl ("",hclasses,hkvs) ils : bs)) =
-- move identifier from div to header
diff --git a/test/command/6030.md b/test/command/6030.md
index 943150432..44a934a6a 100644
--- a/test/command/6030.md
+++ b/test/command/6030.md
@@ -33,3 +33,46 @@ Four
</section>
</section>
```
+
+```
+% pandoc -t beamer --slide-level=3
+# One
+
+One
+
+## Two
+
+Two
+
+### Three
+
+Three
+
+#### Four
+
+Four
+^D
+\hypertarget{one}{%
+\section{One}\label{one}}
+
+\begin{frame}{One}
+One
+\end{frame}
+
+\hypertarget{two}{%
+\subsection{Two}\label{two}}
+
+\begin{frame}{Two}
+Two
+\end{frame}
+
+\begin{frame}{Three}
+\protect\hypertarget{three}{}
+Three
+
+\begin{block}{Four}
+\protect\hypertarget{four}{}
+Four
+\end{block}
+\end{frame}
+```