diff options
author | Albert Krewinkel <albert+github@zeitkraut.de> | 2016-11-26 21:43:46 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2016-11-26 21:43:46 +0100 |
commit | baa25362a40fe905368f60222ebd8a533bcfe0f9 (patch) | |
tree | ece4b41a72bd97e3fb32ba838c21e709bb936de4 /src/Text/Pandoc/Writers | |
parent | 2873cd82886d1fa557bf3abde37b5ceb3cadf40c (diff) | |
download | pandoc-baa25362a40fe905368f60222ebd8a533bcfe0f9.tar.gz |
Allow to overwrite top-level division type heuristics (#3258)
Pandoc uses heuristics to determine the most resonable top-level
division type when emitting LaTeX or Docbook markup. It is now possible
to overwrite this implicitly set top-level division via the
`top-level-division` command line parameter.
API change (`Text.Pandoc.Options`): the type of the
`writerTopLevelDivision` field in of the `WriterOptions` data type is
altered from `Division` to `Maybe Division`. The field's default value
is changed from `Section` to `Nothing`.
Closes: #3197
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/TEI.hs | 3 |
4 files changed, 17 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 6d66ce48c..8e6faefe2 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -37,7 +37,7 @@ import Text.Pandoc.Walk (query) import Text.Printf ( printf ) import Data.List ( intercalate, intersperse ) import Data.Char ( ord ) -import Data.Maybe ( catMaybes ) +import Data.Maybe ( catMaybes, fromMaybe ) import Control.Monad.State import Text.Pandoc.Pretty import Text.Pandoc.ImageSize @@ -84,9 +84,10 @@ pandocToConTeXt options (Pandoc meta blocks) = do let context = defField "toc" (writerTableOfContents options) $ defField "placelist" (intercalate ("," :: String) $ take (writerTOCDepth options + - if writerTopLevelDivision options < Section - then 0 - else 1) + case writerTopLevelDivision options of + Just Part -> 0 + Just Chapter -> 0 + _ -> 1) ["chapter","section","subsection","subsubsection", "subsubsubsection","subsubsubsubsection"]) $ defField "body" main @@ -422,7 +423,7 @@ sectionHeader (ident,classes,_) hdrLevel lst = do contents <- inlineListToConTeXt lst st <- get let opts = stOptions st - let level' = case writerTopLevelDivision opts of + let level' = case fromMaybe Section (writerTopLevelDivision opts) of Part -> hdrLevel - 2 Chapter -> hdrLevel - 1 Section -> hdrLevel diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index c28056153..6dc2c3a4b 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -39,6 +39,7 @@ import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Readers.TeXMath import Data.List ( stripPrefix, isPrefixOf, intercalate, isSuffixOf ) import Data.Char ( toLower ) +import Data.Maybe ( fromMaybe, isNothing ) import Data.Monoid ( Any(..) ) import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Pretty @@ -81,11 +82,11 @@ writeDocbook opts (Pandoc meta blocks) = else Nothing render' = render colwidth opts' = if ("/book>" `isSuffixOf` (trimr $ writerTemplate opts) && - writerTopLevelDivision opts >= Section) - then opts{ writerTopLevelDivision = Chapter } + isNothing (writerTopLevelDivision opts)) + then opts{ writerTopLevelDivision = Just Chapter } else opts -- The numbering here follows LaTeX's internal numbering - startLvl = case writerTopLevelDivision opts' of + startLvl = case fromMaybe Section (writerTopLevelDivision opts') of Part -> -1 Chapter -> 0 Section -> 1 diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 52740ebe7..b75f56cef 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -88,7 +88,10 @@ writeLaTeX options document = stTable = False, stStrikeout = False, stUrl = False, stGraphics = False, stLHS = False, - stBook = writerTopLevelDivision options < Section, + stBook = (case writerTopLevelDivision options of + Just Part -> True + Just Chapter -> True + _ -> False), stCsquotes = False, stHighlighting = False, stIncremental = writerIncremental options, stInternalLinks = [], stUsesEuro = False } @@ -758,7 +761,7 @@ sectionHeader unnumbered ident level lst = do <> braces (text plain)) book <- gets stBook opts <- gets stOptions - let topLevelDivision = min (if book then Chapter else Section) + let topLevelDivision = fromMaybe (if book then Chapter else Section) (writerTopLevelDivision opts) let level' = if writerBeamer opts && topLevelDivision < Section -- beamer has parts but no chapters diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 6120330ca..4b3a205a1 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -36,6 +36,7 @@ import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Templates (renderTemplate') import Data.List ( stripPrefix, isPrefixOf ) +import Data.Maybe ( fromMaybe ) import Data.Char ( toLower ) import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Pretty @@ -60,7 +61,7 @@ writeTEI opts (Pandoc meta blocks) = then Just $ writerColumns opts else Nothing render' = render colwidth - startLvl = case writerTopLevelDivision opts of + startLvl = case fromMaybe Section (writerTopLevelDivision opts) of Part -> -1 Chapter -> 0 Section -> 1 |