diff options
-rw-r--r-- | pandoc.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Options.hs | 4 | ||||
-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 | ||||
-rw-r--r-- | tests/Tests/Writers/Docbook.hs | 2 | ||||
-rw-r--r-- | tests/Tests/Writers/LaTeX.hs | 4 |
8 files changed, 26 insertions, 20 deletions
@@ -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" diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 6c7dde488..b890d1b9a 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -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 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 diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs index 0e80bcc05..f2a1e9d7b 100644 --- a/tests/Tests/Writers/Docbook.hs +++ b/tests/Tests/Writers/Docbook.hs @@ -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>" diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs index 28d6618c1..fb230e89a 100644 --- a/tests/Tests/Writers/LaTeX.hs +++ b/tests/Tests/Writers/LaTeX.hs @@ -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 =?> |