diff options
author | John MacFarlane <jgm@berkeley.edu> | 2016-10-19 14:07:44 +0200 |
---|---|---|
committer | GitHub <noreply@github.com> | 2016-10-19 14:07:44 +0200 |
commit | 1da40d63b13c46782046b03baa92c4f95f3b2a67 (patch) | |
tree | abd52fd31a8904eba423ed17cff81a4ccc9807be /src/Text/Pandoc | |
parent | 29cbd5cbcfd15c67fdb9d82105e18ae7a418358a (diff) | |
parent | 595a171407debfa67436e13e1390d298a3899e74 (diff) | |
download | pandoc-1da40d63b13c46782046b03baa92c4f95f3b2a67.tar.gz |
Merge pull request #3108 from tarleb/part
Add command line option allowing to set type of top-level divisions
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Options.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 36 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 23 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 17 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/TEI.hs | 21 |
5 files changed, 68 insertions, 40 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 39d314974..575250b9e 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -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,7 +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 + , 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 @@ -421,7 +428,7 @@ instance Default WriterOptions where , writerHtmlQTags = False , writerBeamer = False , writerSlideLevel = Nothing - , writerChapters = False + , writerTopLevelDivision = Section , writerListings = False , writerHighlight = False , writerHighlightStyle = pygments diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 398d4170f..6d66ce48c 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -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 (=='-') diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index e19b4666b..c28056153 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -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 [] diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 517460f5d..0fd8cdd8c 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -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,10 +751,18 @@ sectionHeader unnumbered ident level lst = do <> braces (text plain)) book <- gets stBook opts <- gets stOptions - let level' = if book || writerChapters opts then level - 1 else level + 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 | writerBeamer opts -> "part" - | otherwise -> "chapter" + -1 -> "part" + 0 -> "chapter" 1 -> "section" 2 -> "subsection" 3 -> "subsubsection" diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 018884202..6120330ca 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -35,7 +35,7 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Templates (renderTemplate') -import Data.List ( stripPrefix, isPrefixOf, isSuffixOf ) +import Data.List ( stripPrefix, isPrefixOf ) import Data.Char ( toLower ) import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Pretty @@ -60,19 +60,18 @@ writeTEI opts (Pandoc meta blocks) = 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 + 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 (Just . render colwidth . (vcat . - (map (elementToTEI opts' startLvl)) . hierarchicalize)) - (Just . render colwidth . inlinesToTEI opts') + (map (elementToTEI opts startLvl)) . hierarchicalize)) + (Just . render colwidth . inlinesToTEI opts) meta' - main = render' $ vcat (map (elementToTEI opts' startLvl) elements) + main = render' $ vcat (map (elementToTEI opts startLvl) elements) context = defField "body" main $ defField "mathml" (case writerHTMLMathMethod opts of MathML _ -> True @@ -90,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')] $ |