Skip to content

Commit

Permalink
LaTeX writer: fix spacing issue with list in definition list.
Browse files Browse the repository at this point in the history
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[]`.
  • Loading branch information
jgm committed Sep 16, 2020
1 parent a2d3434 commit a26ec96
Show file tree
Hide file tree
Showing 2 changed files with 87 additions and 3 deletions.
23 changes: 20 additions & 3 deletions src/Text/Pandoc/Writers/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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})
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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'
Expand Down
67 changes: 67 additions & 0 deletions test/command/lists-inside-definition.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,67 @@
This inserts an empty `\item[]` when a list occurs at the
beginning of a definition list definition; otherwise the list
may start on the line with the label, which looks terrible.
See https://tex.stackexchange.com/questions/192480/force-itemize-inside-description-onto-a-new-line

```
% pandoc -t latex
Definition
: 1. list
2. list
^D
\begin{description}
\item[Definition]
\begin{enumerate}
\def\labelenumi{\arabic{enumi}.}
\tightlist
\item[]
\item
list
\item
list
\end{enumerate}
\end{description}
```

```
% pandoc -t latex
Definition
: Foo
1. list
2. list
^D
\begin{description}
\item[Definition]
Foo
\begin{enumerate}
\def\labelenumi{\arabic{enumi}.}
\tightlist
\item
list
\item
list
\end{enumerate}
\end{description}
```

```
% pandoc -t latex
Definition
: - list
- list
^D
\begin{description}
\item[Definition]
\begin{itemize}
\tightlist
\item[]
\item
list
\item
list
\end{itemize}
\end{description}
```

0 comments on commit a26ec96

Please sign in to comment.