aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-09-15 17:47:57 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2020-09-15 17:59:03 -0700
commita26ec96d89ccf532f7bca7591c96ba30d8544e4a (patch)
treefd625998ed257e00c7ca6205cf07e38fe26323e1 /src
parenta2d343420f61591ab1ff82ff4e9db8e87542b6ee (diff)
downloadpandoc-a26ec96d89ccf532f7bca7591c96ba30d8544e4a.tar.gz
LaTeX writer: fix spacing issue with list in definition list.
When a list occurs at the beginning of a definition list definition, it can start on the same line as the label, which looks bad. Fix that by starting such lists with an `\item[]`.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs23
1 files changed, 20 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 071a288e1..228b34d09 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -72,6 +72,7 @@ data WriterState =
, stEmptyLine :: Bool -- true if no content on line
, stHasCslRefs :: Bool -- has a Div with class refs
, stCslHangingIndent :: Bool -- use hanging indent for bib
+ , stIsFirstInDefinition :: Bool -- first block in a defn list
}
startingState :: WriterOptions -> WriterState
@@ -102,7 +103,8 @@ startingState options = WriterState {
, stBeamer = False
, stEmptyLine = True
, stHasCslRefs = False
- , stCslHangingIndent = False }
+ , stCslHangingIndent = False
+ , stIsFirstInDefinition = False }
-- | Convert Pandoc to LaTeX.
writeLaTeX :: PandocMonad m => WriterOptions -> Pandoc -> m Text
@@ -682,19 +684,25 @@ blockToLaTeX b@(RawBlock f x) = do
blockToLaTeX (BulletList []) = return empty -- otherwise latex error
blockToLaTeX (BulletList lst) = do
incremental <- gets stIncremental
+ isFirstInDefinition <- gets stIsFirstInDefinition
beamer <- gets stBeamer
let inc = if beamer && incremental then "[<+->]" else ""
items <- mapM listItemToLaTeX lst
let spacing = if isTightList lst
then text "\\tightlist"
else empty
- return $ text ("\\begin{itemize}" <> inc) $$ spacing $$ vcat items $$
+ return $ text ("\\begin{itemize}" <> inc) $$
+ spacing $$
+ -- force list at beginning of definition to start on new line
+ (if isFirstInDefinition then "\\item[]" else mempty) $$
+ vcat items $$
"\\end{itemize}"
blockToLaTeX (OrderedList _ []) = return empty -- otherwise latex error
blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
st <- get
let inc = if stBeamer st && stIncremental st then "[<+->]" else ""
let oldlevel = stOLLevel st
+ isFirstInDefinition <- gets stIsFirstInDefinition
put $ st {stOLLevel = oldlevel + 1}
items <- mapM listItemToLaTeX lst
modify (\s -> s {stOLLevel = oldlevel})
@@ -738,6 +746,8 @@ blockToLaTeX (OrderedList (start, numstyle, numdelim) lst) = do
$$ stylecommand
$$ resetcounter
$$ spacing
+ -- force list at beginning of definition to start on new line
+ $$ (if isFirstInDefinition then "\\item[]" else mempty)
$$ vcat items
$$ "\\end{enumerate}"
blockToLaTeX (DefinitionList []) = return empty
@@ -948,7 +958,14 @@ defListItemToLaTeX (term, defs) = do
let term'' = if any isInternalLink term
then braces term'
else term'
- def' <- liftM vsep $ mapM blockListToLaTeX defs
+ def' <- case concat defs of
+ [] -> return mempty
+ (x:xs) -> do
+ modify $ \s -> s{stIsFirstInDefinition = True }
+ firstitem <- blockToLaTeX x
+ modify $ \s -> s{stIsFirstInDefinition = False }
+ rest <- blockListToLaTeX xs
+ return $ firstitem $+$ rest
return $ case defs of
((Header{} : _) : _) ->
"\\item" <> brackets term'' <> " ~ " $$ def'