Add option for top-level division type

The `--chapters` option is replaced with `--top-level-division` which allows
users to specify the type as which top-level headers should be output. Possible
values are `section` (the default), `chapter`, or `part`.

The formats LaTeX, ConTeXt, and Docbook allow `part` as top-level division, TEI
only allows to set the `type` attribute on `div` containers.  The writers are
altered to respect this option in a sensible way.
This commit is contained in:
Albert Krewinkel 2016-10-19 13:12:57 +02:00
parent aca695ab0b
commit 595a171407
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
9 changed files with 209 additions and 76 deletions

View file

@ -661,16 +661,19 @@ Options affecting specific writers
`--chapters`
: Treat top-level headers as chapters in LaTeX, ConTeXt, and DocBook
output. When the LaTeX document class is set to `report`, `book`,
or `memoir` (unless the `article` option is specified), this
option is implied. If `beamer` is the output format, top-level
headers will become `\part{..}`.
: Deprecated synonym for `--top-level-division=chapter`.
`--parts`
: Treat top-level headers as parts in LaTeX output. The second level
headers will be chapters, i.e. `--chapters` is implied. This does not
effect the `beamer` output format.
`--top-level-division=[section|chapter|part]`
: Treat top-level headers as the given division type in LaTeX, ConTeXt,
DocBook, and TEI output. The hierarchy order is part, chapter, then section;
all headers are shifted such that the top-level header becomes the specified
type. The default is `section`. When the LaTeX document class is set to
`report`, `book`, or `memoir` (unless the `article` option is specified),
`chapter` is implied as the setting for this option. If `beamer` is the
output format, specifying either `chapter` or `part` will cause top-level
headers to become `\part{..}`, while second-level headers remain as their
default type.
`-N`, `--number-sections`

View file

@ -183,8 +183,7 @@ data Opt = Opt
, optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
, optHighlight :: Bool -- ^ Highlight source code
, optHighlightStyle :: Style -- ^ Style to use for highlighted code
, optChapters :: Bool -- ^ Use chapter for top-level sects
, optParts :: Bool -- ^ Use parts for top-level sects in latex
, optTopLevelDivision :: 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
@ -249,8 +248,7 @@ defaultOpts = Opt
, optHtmlQTags = False
, optHighlight = True
, optHighlightStyle = pygments
, optChapters = False
, optParts = False
, optTopLevelDivision = Section
, optHTMLMathMethod = PlainMath
, optReferenceODT = Nothing
, optReferenceDocx = Nothing
@ -608,13 +606,18 @@ options =
, Option "" ["chapters"]
(NoArg
(\opt -> return opt { optChapters = True }))
(\opt -> do warn $ "--chapters is deprecated. " ++
"Use --top-level-divison=chapter instead."
return opt { optTopLevelDivision = Chapter }))
"" -- "Use chapter for top-level sections in LaTeX, DocBook"
, Option "" ["parts"]
(NoArg
(\opt -> return opt { optParts = True }))
"" -- "Use part for top-level sections in LaTeX"
, Option "" ["top-level-division"]
(ReqArg
(\arg opt -> case safeRead (uppercaseFirstLetter arg) of
Just dvsn -> return opt { optTopLevelDivision = dvsn }
_ -> err 76 "could not parse top-level division")
"[section|chapter|part]")
"" -- "Use top-level division type in LaTeX, ConTeXt, DocBook"
, Option "N" ["number-sections"]
(NoArg
@ -1129,9 +1132,8 @@ convertWithOpts opts args = do
, optHtmlQTags = htmlQTags
, optHighlight = highlight
, optHighlightStyle = highlightStyle
, optChapters = chapters
, optTopLevelDivision = topLevelDivision
, optHTMLMathMethod = mathMethod'
, optParts = parts
, optReferenceODT = referenceODT
, optReferenceDocx = referenceDocx
, optEpubStylesheet = epubStylesheet
@ -1394,8 +1396,7 @@ convertWithOpts opts args = do
writerUserDataDir = datadir,
writerHtml5 = html5,
writerHtmlQTags = htmlQTags,
writerChapters = chapters,
writerParts = parts,
writerTopLevelDivision = topLevelDivision,
writerListings = listings,
writerBeamer = False,
writerSlideLevel = slideLevel,

View file

@ -43,6 +43,7 @@ module Text.Pandoc.Options ( Extension(..)
, HTMLSlideVariant (..)
, EPUBVersion (..)
, WrapOption (..)
, Division (..)
, WriterOptions (..)
, TrackChanges (..)
, ReferenceLocation (..)
@ -337,6 +338,12 @@ data WrapOption = WrapAuto -- ^ Automatically wrap to width
| WrapPreserve -- ^ Preserve wrapping of input source
deriving (Show, Read, Eq, Data, Typeable, Generic)
-- | Options defining the type of top-level headers.
data Division = Part -- ^ Top-level headers become parts
| Chapter -- ^ Top-level headers become chapters
| Section -- ^ Top-level headers become sections
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
-- | Locations for footnotes and references in markdown output
data ReferenceLocation = EndOfBlock -- ^ End of block
| EndOfSection -- ^ prior to next section header (or end of document)
@ -373,8 +380,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
, writerChapters :: Bool -- ^ Use "chapter" for top-level sects
, writerParts :: Bool -- ^ Use "part" for top-level sects in LaTeX
, writerTopLevelDivision :: 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
@ -422,8 +428,7 @@ instance Default WriterOptions where
, writerHtmlQTags = False
, writerBeamer = False
, writerSlideLevel = Nothing
, writerChapters = False
, writerParts = False
, writerTopLevelDivision = Section
, writerListings = False
, writerHighlight = False
, writerHighlightStyle = pygments

View file

@ -83,9 +83,10 @@ pandocToConTeXt options (Pandoc meta blocks) = do
]
let context = defField "toc" (writerTableOfContents options)
$ defField "placelist" (intercalate ("," :: String) $
take (writerTOCDepth options + if writerChapters options
then 0
else 1)
take (writerTOCDepth options +
if writerTopLevelDivision options < Section
then 0
else 1)
["chapter","section","subsection","subsubsection",
"subsubsubsection","subsubsubsubsection"])
$ defField "body" main
@ -412,7 +413,7 @@ inlineToConTeXt (Span (_,_,kvs) ils) = do
Nothing -> txt
fmap (wrapLang . wrapDir) $ inlineListToConTeXt ils
-- | Craft the section header, inserting the secton reference, if supplied.
-- | Craft the section header, inserting the section reference, if supplied.
sectionHeader :: Attr
-> Int
-> [Inline]
@ -421,21 +422,26 @@ sectionHeader (ident,classes,_) hdrLevel lst = do
contents <- inlineListToConTeXt lst
st <- get
let opts = stOptions st
let level' = if writerChapters opts then hdrLevel - 1 else hdrLevel
let level' = case writerTopLevelDivision opts of
Part -> hdrLevel - 2
Chapter -> hdrLevel - 1
Section -> hdrLevel
let ident' = toLabel ident
let (section, chapter) = if "unnumbered" `elem` classes
then (text "subject", text "title")
else (text "section", text "chapter")
return $ if level' >= 1 && level' <= 5
then char '\\'
<> text (concat (replicate (level' - 1) "sub"))
<> section
<> (if (not . null) ident' then brackets (text ident') else empty)
<> braces contents
<> blankline
else if level' == 0
then char '\\' <> chapter <> braces contents
else contents <> blankline
return $ case level' of
-1 -> text "\\part" <> braces contents
0 -> char '\\' <> chapter <> braces contents
n | n >= 1 && n <= 5 -> char '\\'
<> text (concat (replicate (n - 1) "sub"))
<> section
<> (if (not . null) ident'
then brackets (text ident')
else empty)
<> braces contents
<> blankline
_ -> contents <> blankline
fromBcp47' :: String -> String
fromBcp47' = fromBcp47 . splitBy (=='-')

View file

@ -79,12 +79,16 @@ writeDocbook opts (Pandoc meta blocks) =
colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
render' = render colwidth
opts' = if "/book>" `isSuffixOf`
(trimr $ writerTemplate opts)
then opts{ writerChapters = True }
else opts
startLvl = if writerChapters opts' then 0 else 1
render' = render colwidth
opts' = if ("/book>" `isSuffixOf` (trimr $ writerTemplate opts) &&
writerTopLevelDivision opts >= Section)
then opts{ writerTopLevelDivision = Chapter }
else opts
-- The numbering here follows LaTeX's internal numbering
startLvl = case writerTopLevelDivision opts' of
Part -> -1
Chapter -> 0
Section -> 1
auths' = map (authorToDocbook opts) $ docAuthors meta
meta' = B.setMeta "author" auths' meta
Just metadata = metaToJSON opts
@ -111,11 +115,12 @@ elementToDocbook opts lvl (Sec _ _num (id',_,_) title elements) =
then [Blk (Para [])]
else elements
tag = case lvl of
n | n == 0 -> "chapter"
| n >= 1 && n <= 5 -> if writerDocbook5 opts
-1 -> "part"
0 -> "chapter"
n | n >= 1 && n <= 5 -> if writerDocbook5 opts
then "section"
else "sect" ++ show n
| otherwise -> "simplesect"
_ -> "simplesect"
idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')]
nsAttr = if writerDocbook5 opts && lvl == 0 then [("xmlns", "http://docbook.org/ns/docbook"),("xmlns:xlink", "http://www.w3.org/1999/xlink")]
else []

View file

@ -87,7 +87,8 @@ writeLaTeX options document =
stOptions = options, stVerbInNote = False,
stTable = False, stStrikeout = False,
stUrl = False, stGraphics = False,
stLHS = False, stBook = writerChapters options,
stLHS = False,
stBook = writerTopLevelDivision options < Section,
stCsquotes = False, stHighlighting = False,
stIncremental = writerIncremental options,
stInternalLinks = [], stUsesEuro = False }
@ -750,25 +751,26 @@ sectionHeader unnumbered ident level lst = do
<> braces (text plain))
book <- gets stBook
opts <- gets stOptions
let level' = case level of
1 | writerParts opts -> 0
| writerBeamer opts -> 0
| book || writerChapters opts -> 1
| otherwise -> 2
_ | writerParts opts -> level - 1
| book || writerChapters opts -> level
| otherwise -> level + 1
let topLevelDivision = min (if book then Chapter else Section)
(writerTopLevelDivision opts)
let level' = if writerBeamer opts && topLevelDivision < Section
-- beamer has parts but no chapters
then if level == 1 then -1 else level - 1
else case topLevelDivision of
Part -> level - 2
Chapter -> level - 1
Section -> level
let sectionType = case level' of
0 -> "part"
1 -> "chapter"
2 -> "section"
3 -> "subsection"
4 -> "subsubsection"
5 -> "paragraph"
6 -> "subparagraph"
-1 -> "part"
0 -> "chapter"
1 -> "section"
2 -> "subsection"
3 -> "subsubsection"
4 -> "paragraph"
5 -> "subparagraph"
_ -> ""
inQuote <- gets stInQuote
let prefix = if inQuote && level' >= 5
let prefix = if inQuote && level' >= 4
then text "\\mbox{}%"
-- needed for \paragraph, \subparagraph in quote environment
-- see http://tex.stackexchange.com/questions/169830/
@ -777,7 +779,7 @@ sectionHeader unnumbered ident level lst = do
let star = if unnumbered && level < 4 then text "*" else empty
let stuffing = star <> optional <> contents
stuffing' <- hypertarget ident $ text ('\\':sectionType) <> stuffing <> lab
return $ if level' > 6
return $ if level' > 5
then txt
else prefix $$ stuffing'
$$ if unnumbered

View file

@ -60,7 +60,10 @@ writeTEI opts (Pandoc meta blocks) =
then Just $ writerColumns opts
else Nothing
render' = render colwidth
startLvl = if writerChapters opts then 0 else 1
startLvl = case writerTopLevelDivision opts of
Part -> -1
Chapter -> 0
Section -> 1
auths' = map (authorToTEI opts) $ docAuthors meta
meta' = B.setMeta "author" auths' meta
Just metadata = metaToJSON opts
@ -86,8 +89,10 @@ elementToTEI opts lvl (Sec _ _num (id',_,_) title elements) =
let elements' = if null elements
then [Blk (Para [])]
else elements
-- level numbering correspond to LaTeX internals
divType = case lvl of
n | n == 0 -> "chapter"
n | n == -1 -> "part"
| n == 0 -> "chapter"
| n >= 1 && n <= 5 -> "level" ++ show n
| otherwise -> "section"
in inTags True "div" [("type", divType) | not (null id')] $

View file

@ -8,7 +8,10 @@ import Tests.Helpers
import Text.Pandoc.Arbitrary()
docbook :: (ToPandoc a) => a -> String
docbook = writeDocbook def{ writerWrapText = WrapNone } . toPandoc
docbook = docbookWithOpts def{ writerWrapText = WrapNone }
docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
docbookWithOpts opts = writeDocbook opts . toPandoc
{-
"my test" =: X =?> Y
@ -226,4 +229,56 @@ tests = [ testGroup "line blocks"
]
]
]
, testGroup "writer options" $
[ testGroup "top-level division" $
let
headers = header 1 (text "header1")
<> header 2 (text "header2")
<> header 3 (text "header3")
docbookTopLevelDiv :: (ToPandoc a) => Division -> a -> String
docbookTopLevelDiv division =
docbookWithOpts def{ writerTopLevelDivision = division }
in
[ test (docbookTopLevelDiv Section) "sections as top-level" $ headers =?>
unlines [ "<sect1>"
, " <title>header1</title>"
, " <sect2>"
, " <title>header2</title>"
, " <sect3>"
, " <title>header3</title>"
, " <para>"
, " </para>"
, " </sect3>"
, " </sect2>"
, "</sect1>"
]
, test (docbookTopLevelDiv Chapter) "chapters as top-level" $ headers =?>
unlines [ "<chapter>"
, " <title>header1</title>"
, " <sect1>"
, " <title>header2</title>"
, " <sect2>"
, " <title>header3</title>"
, " <para>"
, " </para>"
, " </sect2>"
, " </sect1>"
, "</chapter>"
]
, test (docbookTopLevelDiv Part) "parts as top-level" $ headers =?>
unlines [ "<part>"
, " <title>header1</title>"
, " <chapter>"
, " <title>header2</title>"
, " <sect1>"
, " <title>header3</title>"
, " <para>"
, " </para>"
, " </sect1>"
, " </chapter>"
, "</part>"
]
]
]
]

View file

@ -2,16 +2,19 @@
module Tests.Writers.LaTeX (tests) where
import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
import Text.Pandoc.Arbitrary()
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
latex :: (ToPandoc a) => a -> String
latex = writeLaTeX def{ writerHighlight = True } . toPandoc
latex = latexWithOpts def{ writerHighlight = True }
latexListing :: (ToPandoc a) => a -> String
latexListing = writeLaTeX def{ writerListings = True } . toPandoc
latexListing = latexWithOpts def{ writerListings = True }
latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
latexWithOpts opts = writeLaTeX opts . toPandoc
{-
"my test" =: X =?> Y
@ -78,4 +81,52 @@ tests = [ testGroup "code blocks"
, "backtick" =:
code "`nu?`" =?> "\\texttt{\\textasciigrave{}nu?\\textasciigrave{}}"
]
, testGroup "writer options"
[ testGroup "top-level division" $
let
headers = header 1 (text "header1")
<> header 2 (text "header2")
<> header 3 (text "header3")
latexTopLevelDiv :: (ToPandoc a) => Division -> a -> String
latexTopLevelDiv division =
latexWithOpts def{ writerTopLevelDivision = division }
beamerTopLevelDiv :: (ToPandoc a) => Division -> a -> String
beamerTopLevelDiv division =
latexWithOpts def { writerTopLevelDivision = division
, writerBeamer = True }
in
[ test (latexTopLevelDiv Section) "sections as top-level" $ headers =?>
unlines [ "\\section{header1}\n"
, "\\subsection{header2}\n"
, "\\subsubsection{header3}"
]
, test (latexTopLevelDiv Chapter) "chapters as top-level" $ headers =?>
unlines [ "\\chapter{header1}\n"
, "\\section{header2}\n"
, "\\subsection{header3}"
]
, test (latexTopLevelDiv Part) "parts as top-level" $ headers =?>
unlines [ "\\part{header1}\n"
, "\\chapter{header2}\n"
, "\\section{header3}"
]
, test (beamerTopLevelDiv Section) "sections as top-level in beamer" $ headers =?>
unlines [ "\\section{header1}\n"
, "\\subsection{header2}\n"
, "\\subsubsection{header3}"
]
, test (beamerTopLevelDiv Chapter) "chapters are as part in beamer" $ headers =?>
unlines [ "\\part{header1}\n"
, "\\section{header2}\n"
, "\\subsection{header3}"
]
, test (beamerTopLevelDiv Part) "parts as top-level in beamer" $ headers =?>
unlines [ "\\part{header1}\n"
, "\\section{header2}\n"
, "\\subsection{header3}"
]
]
]
]