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
This commit is contained in:
Albert Krewinkel 2016-11-26 21:43:46 +01:00 committed by John MacFarlane
parent 2873cd8288
commit baa25362a4
8 changed files with 26 additions and 20 deletions

View file

@ -181,7 +181,7 @@ data Opt = Opt
, optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
, optHighlight :: Bool -- ^ Highlight source code
, optHighlightStyle :: Style -- ^ Style to use for highlighted code
, optTopLevelDivision :: Division -- ^ Type of the top-level divisions
, optTopLevelDivision :: Maybe Division -- ^ Type of the top-level divisions
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
, optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
@ -246,7 +246,7 @@ defaultOpts = Opt
, optHtmlQTags = False
, optHighlight = True
, optHighlightStyle = pygments
, optTopLevelDivision = Section
, optTopLevelDivision = Nothing
, optHTMLMathMethod = PlainMath
, optReferenceODT = Nothing
, optReferenceDocx = Nothing
@ -598,13 +598,13 @@ options =
(NoArg
(\opt -> do warn $ "--chapters is deprecated. " ++
"Use --top-level-division=chapter instead."
return opt { optTopLevelDivision = Chapter }))
return opt { optTopLevelDivision = Just Chapter }))
"" -- "Use chapter for top-level sections in LaTeX, DocBook"
, Option "" ["top-level-division"]
(ReqArg
(\arg opt -> case safeRead (uppercaseFirstLetter arg) of
Just dvsn -> return opt { optTopLevelDivision = dvsn }
Just dvsn -> return opt { optTopLevelDivision = Just dvsn }
_ -> err 76 "Top-level division must be section, chapter, or part")
"[section|chapter|part]")
"" -- "Use top-level division type in LaTeX, ConTeXt, DocBook"

View file

@ -382,7 +382,7 @@ data WriterOptions = WriterOptions
, writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
, writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show
, writerSlideLevel :: Maybe Int -- ^ Force header level of slides
, writerTopLevelDivision :: Division -- ^ Type of top-level divisions
, writerTopLevelDivision :: Maybe Division -- ^ Type of top-level divisions
, writerListings :: Bool -- ^ Use listings package for code
, writerHighlight :: Bool -- ^ Highlight source code
, writerHighlightStyle :: Style -- ^ Style to use for highlighting
@ -430,7 +430,7 @@ instance Default WriterOptions where
, writerHtmlQTags = False
, writerBeamer = False
, writerSlideLevel = Nothing
, writerTopLevelDivision = Section
, writerTopLevelDivision = Nothing
, writerListings = False
, writerHighlight = False
, writerHighlightStyle = pygments

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -238,7 +238,7 @@ tests = [ testGroup "line blocks"
docbookTopLevelDiv :: (ToPandoc a) => Division -> a -> String
docbookTopLevelDiv division =
docbookWithOpts def{ writerTopLevelDivision = division }
docbookWithOpts def{ writerTopLevelDivision = Just division }
in
[ test (docbookTopLevelDiv Section) "sections as top-level" $ headers =?>
unlines [ "<sect1>"

View file

@ -90,11 +90,11 @@ tests = [ testGroup "code blocks"
latexTopLevelDiv :: (ToPandoc a) => Division -> a -> String
latexTopLevelDiv division =
latexWithOpts def{ writerTopLevelDivision = division }
latexWithOpts def{ writerTopLevelDivision = Just division }
beamerTopLevelDiv :: (ToPandoc a) => Division -> a -> String
beamerTopLevelDiv division =
latexWithOpts def { writerTopLevelDivision = division
latexWithOpts def { writerTopLevelDivision = Just division
, writerBeamer = True }
in
[ test (latexTopLevelDiv Section) "sections as top-level" $ headers =?>