Refactor top-level division selection (#3261)
The "default" option is no longer represented as `Nothing` but via a new type constructor, making the `Maybe` wrapper superfluous. The default behavior of using heuristics can now be enabled explicitly by setting `--top-level-division=default`. API change (`Text.Pandoc.Options`): The `Division` type was renamed to `TopLevelDivision`. The `Section`, `Chapter`, and `Part` constructors were renamed to `TopLevelSection`, `TopLevelChapter`, and `TopLevelPart`, respectively. An additional `TopLevelDefault` constructor was added, which is now also the new default value of the `writerTopLevelDivision` field in `WriterOptions`.
This commit is contained in:
parent
08bf8f2e9d
commit
1fc07ff4da
9 changed files with 111 additions and 64 deletions
15
MANUAL.txt
15
MANUAL.txt
|
@ -684,17 +684,18 @@ Options affecting specific writers
|
||||||
|
|
||||||
: Deprecated synonym for `--top-level-division=chapter`.
|
: Deprecated synonym for `--top-level-division=chapter`.
|
||||||
|
|
||||||
`--top-level-division=[section|chapter|part]`
|
`--top-level-division=[default|section|chapter|part]`
|
||||||
|
|
||||||
: Treat top-level headers as the given division type in LaTeX, ConTeXt,
|
: Treat top-level headers as the given division type in LaTeX, ConTeXt,
|
||||||
DocBook, and TEI output. The hierarchy order is part, chapter, then section;
|
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
|
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
|
type. The default behavior is to determine the best division type via
|
||||||
`report`, `book`, or `memoir` (unless the `article` option is specified),
|
heuristics: unless other conditions apply, `section` is chosen. When the
|
||||||
`chapter` is implied as the setting for this option. If `beamer` is the
|
LaTeX document class is set to `report`, `book`, or `memoir` (unless the
|
||||||
output format, specifying either `chapter` or `part` will cause top-level
|
`article` option is specified), `chapter` is implied as the setting for this
|
||||||
headers to become `\part{..}`, while second-level headers remain as their
|
option. If `beamer` is the output format, specifying either `chapter` or
|
||||||
default type.
|
`part` will cause top-level headers to become `\part{..}`, while
|
||||||
|
second-level headers remain as their default type.
|
||||||
|
|
||||||
`-N`, `--number-sections`
|
`-N`, `--number-sections`
|
||||||
|
|
||||||
|
|
15
pandoc.hs
15
pandoc.hs
|
@ -181,7 +181,7 @@ data Opt = Opt
|
||||||
, optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
|
, optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
|
||||||
, optHighlight :: Bool -- ^ Highlight source code
|
, optHighlight :: Bool -- ^ Highlight source code
|
||||||
, optHighlightStyle :: Style -- ^ Style to use for highlighted code
|
, optHighlightStyle :: Style -- ^ Style to use for highlighted code
|
||||||
, optTopLevelDivision :: Maybe Division -- ^ Type of the top-level divisions
|
, optTopLevelDivision :: TopLevelDivision -- ^ Type of the top-level divisions
|
||||||
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
|
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
|
||||||
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
|
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
|
||||||
, optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
|
, optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
|
||||||
|
@ -246,7 +246,7 @@ defaultOpts = Opt
|
||||||
, optHtmlQTags = False
|
, optHtmlQTags = False
|
||||||
, optHighlight = True
|
, optHighlight = True
|
||||||
, optHighlightStyle = pygments
|
, optHighlightStyle = pygments
|
||||||
, optTopLevelDivision = Nothing
|
, optTopLevelDivision = TopLevelDefault
|
||||||
, optHTMLMathMethod = PlainMath
|
, optHTMLMathMethod = PlainMath
|
||||||
, optReferenceODT = Nothing
|
, optReferenceODT = Nothing
|
||||||
, optReferenceDocx = Nothing
|
, optReferenceDocx = Nothing
|
||||||
|
@ -598,14 +598,17 @@ options =
|
||||||
(NoArg
|
(NoArg
|
||||||
(\opt -> do warn $ "--chapters is deprecated. " ++
|
(\opt -> do warn $ "--chapters is deprecated. " ++
|
||||||
"Use --top-level-division=chapter instead."
|
"Use --top-level-division=chapter instead."
|
||||||
return opt { optTopLevelDivision = Just Chapter }))
|
return opt { optTopLevelDivision = TopLevelChapter }))
|
||||||
"" -- "Use chapter for top-level sections in LaTeX, DocBook"
|
"" -- "Use chapter for top-level sections in LaTeX, DocBook"
|
||||||
|
|
||||||
, Option "" ["top-level-division"]
|
, Option "" ["top-level-division"]
|
||||||
(ReqArg
|
(ReqArg
|
||||||
(\arg opt -> case safeRead (uppercaseFirstLetter arg) of
|
(\arg opt -> do
|
||||||
Just dvsn -> return opt { optTopLevelDivision = Just dvsn }
|
let tldName = "TopLevel" ++ uppercaseFirstLetter arg
|
||||||
_ -> err 76 "Top-level division must be section, chapter, or part")
|
case safeRead tldName of
|
||||||
|
Just tlDiv -> return opt { optTopLevelDivision = tlDiv }
|
||||||
|
_ -> err 76 ("Top-level division must be " ++
|
||||||
|
"section, chapter, part, or default"))
|
||||||
"[section|chapter|part]")
|
"[section|chapter|part]")
|
||||||
"" -- "Use top-level division type in LaTeX, ConTeXt, DocBook"
|
"" -- "Use top-level division type in LaTeX, ConTeXt, DocBook"
|
||||||
|
|
||||||
|
|
|
@ -43,7 +43,7 @@ module Text.Pandoc.Options ( Extension(..)
|
||||||
, HTMLSlideVariant (..)
|
, HTMLSlideVariant (..)
|
||||||
, EPUBVersion (..)
|
, EPUBVersion (..)
|
||||||
, WrapOption (..)
|
, WrapOption (..)
|
||||||
, Division (..)
|
, TopLevelDivision (..)
|
||||||
, WriterOptions (..)
|
, WriterOptions (..)
|
||||||
, TrackChanges (..)
|
, TrackChanges (..)
|
||||||
, ReferenceLocation (..)
|
, ReferenceLocation (..)
|
||||||
|
@ -341,10 +341,12 @@ data WrapOption = WrapAuto -- ^ Automatically wrap to width
|
||||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||||
|
|
||||||
-- | Options defining the type of top-level headers.
|
-- | Options defining the type of top-level headers.
|
||||||
data Division = Part -- ^ Top-level headers become parts
|
data TopLevelDivision = TopLevelPart -- ^ Top-level headers become parts
|
||||||
| Chapter -- ^ Top-level headers become chapters
|
| TopLevelChapter -- ^ Top-level headers become chapters
|
||||||
| Section -- ^ Top-level headers become sections
|
| TopLevelSection -- ^ Top-level headers become sections
|
||||||
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
|
| TopLevelDefault -- ^ Top-level type is determined via
|
||||||
|
-- heuristics
|
||||||
|
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||||
|
|
||||||
-- | Locations for footnotes and references in markdown output
|
-- | Locations for footnotes and references in markdown output
|
||||||
data ReferenceLocation = EndOfBlock -- ^ End of block
|
data ReferenceLocation = EndOfBlock -- ^ End of block
|
||||||
|
@ -382,7 +384,7 @@ data WriterOptions = WriterOptions
|
||||||
, writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
|
, writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
|
||||||
, writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show
|
, writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show
|
||||||
, writerSlideLevel :: Maybe Int -- ^ Force header level of slides
|
, writerSlideLevel :: Maybe Int -- ^ Force header level of slides
|
||||||
, writerTopLevelDivision :: Maybe Division -- ^ Type of top-level divisions
|
, writerTopLevelDivision :: TopLevelDivision -- ^ Type of top-level divisions
|
||||||
, writerListings :: Bool -- ^ Use listings package for code
|
, writerListings :: Bool -- ^ Use listings package for code
|
||||||
, writerHighlight :: Bool -- ^ Highlight source code
|
, writerHighlight :: Bool -- ^ Highlight source code
|
||||||
, writerHighlightStyle :: Style -- ^ Style to use for highlighting
|
, writerHighlightStyle :: Style -- ^ Style to use for highlighting
|
||||||
|
@ -430,7 +432,7 @@ instance Default WriterOptions where
|
||||||
, writerHtmlQTags = False
|
, writerHtmlQTags = False
|
||||||
, writerBeamer = False
|
, writerBeamer = False
|
||||||
, writerSlideLevel = Nothing
|
, writerSlideLevel = Nothing
|
||||||
, writerTopLevelDivision = Nothing
|
, writerTopLevelDivision = TopLevelDefault
|
||||||
, writerListings = False
|
, writerListings = False
|
||||||
, writerHighlight = False
|
, writerHighlight = False
|
||||||
, writerHighlightStyle = pygments
|
, writerHighlightStyle = pygments
|
||||||
|
|
|
@ -37,7 +37,7 @@ import Text.Pandoc.Walk (query)
|
||||||
import Text.Printf ( printf )
|
import Text.Printf ( printf )
|
||||||
import Data.List ( intercalate, intersperse )
|
import Data.List ( intercalate, intersperse )
|
||||||
import Data.Char ( ord )
|
import Data.Char ( ord )
|
||||||
import Data.Maybe ( catMaybes, fromMaybe )
|
import Data.Maybe ( catMaybes )
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Text.Pandoc.Pretty
|
import Text.Pandoc.Pretty
|
||||||
import Text.Pandoc.ImageSize
|
import Text.Pandoc.ImageSize
|
||||||
|
@ -85,9 +85,9 @@ pandocToConTeXt options (Pandoc meta blocks) = do
|
||||||
$ defField "placelist" (intercalate ("," :: String) $
|
$ defField "placelist" (intercalate ("," :: String) $
|
||||||
take (writerTOCDepth options +
|
take (writerTOCDepth options +
|
||||||
case writerTopLevelDivision options of
|
case writerTopLevelDivision options of
|
||||||
Just Part -> 0
|
TopLevelPart -> 0
|
||||||
Just Chapter -> 0
|
TopLevelChapter -> 0
|
||||||
_ -> 1)
|
_ -> 1)
|
||||||
["chapter","section","subsection","subsubsection",
|
["chapter","section","subsection","subsubsection",
|
||||||
"subsubsubsection","subsubsubsubsection"])
|
"subsubsubsection","subsubsubsubsection"])
|
||||||
$ defField "body" main
|
$ defField "body" main
|
||||||
|
@ -423,10 +423,11 @@ sectionHeader (ident,classes,_) hdrLevel lst = do
|
||||||
contents <- inlineListToConTeXt lst
|
contents <- inlineListToConTeXt lst
|
||||||
st <- get
|
st <- get
|
||||||
let opts = stOptions st
|
let opts = stOptions st
|
||||||
let level' = case fromMaybe Section (writerTopLevelDivision opts) of
|
let level' = case writerTopLevelDivision opts of
|
||||||
Part -> hdrLevel - 2
|
TopLevelPart -> hdrLevel - 2
|
||||||
Chapter -> hdrLevel - 1
|
TopLevelChapter -> hdrLevel - 1
|
||||||
Section -> hdrLevel
|
TopLevelSection -> hdrLevel
|
||||||
|
TopLevelDefault -> hdrLevel
|
||||||
let ident' = toLabel ident
|
let ident' = toLabel ident
|
||||||
let (section, chapter) = if "unnumbered" `elem` classes
|
let (section, chapter) = if "unnumbered" `elem` classes
|
||||||
then (text "subject", text "title")
|
then (text "subject", text "title")
|
||||||
|
|
|
@ -39,7 +39,6 @@ import Text.Pandoc.Templates (renderTemplate')
|
||||||
import Text.Pandoc.Readers.TeXMath
|
import Text.Pandoc.Readers.TeXMath
|
||||||
import Data.List ( stripPrefix, isPrefixOf, intercalate, isSuffixOf )
|
import Data.List ( stripPrefix, isPrefixOf, intercalate, isSuffixOf )
|
||||||
import Data.Char ( toLower )
|
import Data.Char ( toLower )
|
||||||
import Data.Maybe ( fromMaybe, isNothing )
|
|
||||||
import Data.Monoid ( Any(..) )
|
import Data.Monoid ( Any(..) )
|
||||||
import Text.Pandoc.Highlighting ( languages, languagesByExtension )
|
import Text.Pandoc.Highlighting ( languages, languagesByExtension )
|
||||||
import Text.Pandoc.Pretty
|
import Text.Pandoc.Pretty
|
||||||
|
@ -82,14 +81,15 @@ writeDocbook opts (Pandoc meta blocks) =
|
||||||
else Nothing
|
else Nothing
|
||||||
render' = render colwidth
|
render' = render colwidth
|
||||||
opts' = if ("/book>" `isSuffixOf` (trimr $ writerTemplate opts) &&
|
opts' = if ("/book>" `isSuffixOf` (trimr $ writerTemplate opts) &&
|
||||||
isNothing (writerTopLevelDivision opts))
|
TopLevelDefault == writerTopLevelDivision opts)
|
||||||
then opts{ writerTopLevelDivision = Just Chapter }
|
then opts{ writerTopLevelDivision = TopLevelChapter }
|
||||||
else opts
|
else opts
|
||||||
-- The numbering here follows LaTeX's internal numbering
|
-- The numbering here follows LaTeX's internal numbering
|
||||||
startLvl = case fromMaybe Section (writerTopLevelDivision opts') of
|
startLvl = case writerTopLevelDivision opts' of
|
||||||
Part -> -1
|
TopLevelPart -> -1
|
||||||
Chapter -> 0
|
TopLevelChapter -> 0
|
||||||
Section -> 1
|
TopLevelSection -> 1
|
||||||
|
TopLevelDefault -> 1
|
||||||
auths' = map (authorToDocbook opts) $ docAuthors meta
|
auths' = map (authorToDocbook opts) $ docAuthors meta
|
||||||
meta' = B.setMeta "author" auths' meta
|
meta' = B.setMeta "author" auths' meta
|
||||||
Just metadata = metaToJSON opts
|
Just metadata = metaToJSON opts
|
||||||
|
|
|
@ -89,9 +89,9 @@ writeLaTeX options document =
|
||||||
stUrl = False, stGraphics = False,
|
stUrl = False, stGraphics = False,
|
||||||
stLHS = False,
|
stLHS = False,
|
||||||
stBook = (case writerTopLevelDivision options of
|
stBook = (case writerTopLevelDivision options of
|
||||||
Just Part -> True
|
TopLevelPart -> True
|
||||||
Just Chapter -> True
|
TopLevelChapter -> True
|
||||||
_ -> False),
|
_ -> False),
|
||||||
stCsquotes = False, stHighlighting = False,
|
stCsquotes = False, stHighlighting = False,
|
||||||
stIncremental = writerIncremental options,
|
stIncremental = writerIncremental options,
|
||||||
stInternalLinks = [], stUsesEuro = False }
|
stInternalLinks = [], stUsesEuro = False }
|
||||||
|
@ -763,15 +763,18 @@ sectionHeader unnumbered ident level lst = do
|
||||||
<> braces (text plain))
|
<> braces (text plain))
|
||||||
book <- gets stBook
|
book <- gets stBook
|
||||||
opts <- gets stOptions
|
opts <- gets stOptions
|
||||||
let topLevelDivision = fromMaybe (if book then Chapter else Section)
|
let topLevelDivision = if book && writerTopLevelDivision opts == TopLevelDefault
|
||||||
(writerTopLevelDivision opts)
|
then TopLevelChapter
|
||||||
let level' = if writerBeamer opts && topLevelDivision < Section
|
else writerTopLevelDivision opts
|
||||||
|
let level' = if writerBeamer opts &&
|
||||||
|
topLevelDivision `elem` [TopLevelPart, TopLevelChapter]
|
||||||
-- beamer has parts but no chapters
|
-- beamer has parts but no chapters
|
||||||
then if level == 1 then -1 else level - 1
|
then if level == 1 then -1 else level - 1
|
||||||
else case topLevelDivision of
|
else case topLevelDivision of
|
||||||
Part -> level - 2
|
TopLevelPart -> level - 2
|
||||||
Chapter -> level - 1
|
TopLevelChapter -> level - 1
|
||||||
Section -> level
|
TopLevelSection -> level
|
||||||
|
TopLevelDefault -> level
|
||||||
let sectionType = case level' of
|
let sectionType = case level' of
|
||||||
-1 -> "part"
|
-1 -> "part"
|
||||||
0 -> "chapter"
|
0 -> "chapter"
|
||||||
|
|
|
@ -36,7 +36,6 @@ import Text.Pandoc.Writers.Shared
|
||||||
import Text.Pandoc.Options
|
import Text.Pandoc.Options
|
||||||
import Text.Pandoc.Templates (renderTemplate')
|
import Text.Pandoc.Templates (renderTemplate')
|
||||||
import Data.List ( stripPrefix, isPrefixOf )
|
import Data.List ( stripPrefix, isPrefixOf )
|
||||||
import Data.Maybe ( fromMaybe )
|
|
||||||
import Data.Char ( toLower )
|
import Data.Char ( toLower )
|
||||||
import Text.Pandoc.Highlighting ( languages, languagesByExtension )
|
import Text.Pandoc.Highlighting ( languages, languagesByExtension )
|
||||||
import Text.Pandoc.Pretty
|
import Text.Pandoc.Pretty
|
||||||
|
@ -61,10 +60,11 @@ writeTEI opts (Pandoc meta blocks) =
|
||||||
then Just $ writerColumns opts
|
then Just $ writerColumns opts
|
||||||
else Nothing
|
else Nothing
|
||||||
render' = render colwidth
|
render' = render colwidth
|
||||||
startLvl = case fromMaybe Section (writerTopLevelDivision opts) of
|
startLvl = case writerTopLevelDivision opts of
|
||||||
Part -> -1
|
TopLevelPart -> -1
|
||||||
Chapter -> 0
|
TopLevelChapter -> 0
|
||||||
Section -> 1
|
TopLevelSection -> 1
|
||||||
|
TopLevelDefault -> 1
|
||||||
auths' = map (authorToTEI opts) $ docAuthors meta
|
auths' = map (authorToTEI opts) $ docAuthors meta
|
||||||
meta' = B.setMeta "author" auths' meta
|
meta' = B.setMeta "author" auths' meta
|
||||||
Just metadata = metaToJSON opts
|
Just metadata = metaToJSON opts
|
||||||
|
|
|
@ -236,11 +236,13 @@ tests = [ testGroup "line blocks"
|
||||||
<> header 2 (text "header2")
|
<> header 2 (text "header2")
|
||||||
<> header 3 (text "header3")
|
<> header 3 (text "header3")
|
||||||
|
|
||||||
docbookTopLevelDiv :: (ToPandoc a) => Division -> a -> String
|
docbookTopLevelDiv :: (ToPandoc a)
|
||||||
|
=> TopLevelDivision -> a -> String
|
||||||
docbookTopLevelDiv division =
|
docbookTopLevelDiv division =
|
||||||
docbookWithOpts def{ writerTopLevelDivision = Just division }
|
docbookWithOpts def{ writerTopLevelDivision = division }
|
||||||
in
|
in
|
||||||
[ test (docbookTopLevelDiv Section) "sections as top-level" $ headers =?>
|
[ test (docbookTopLevelDiv TopLevelSection) "sections as top-level" $
|
||||||
|
headers =?>
|
||||||
unlines [ "<sect1>"
|
unlines [ "<sect1>"
|
||||||
, " <title>header1</title>"
|
, " <title>header1</title>"
|
||||||
, " <sect2>"
|
, " <sect2>"
|
||||||
|
@ -253,7 +255,8 @@ tests = [ testGroup "line blocks"
|
||||||
, " </sect2>"
|
, " </sect2>"
|
||||||
, "</sect1>"
|
, "</sect1>"
|
||||||
]
|
]
|
||||||
, test (docbookTopLevelDiv Chapter) "chapters as top-level" $ headers =?>
|
, test (docbookTopLevelDiv TopLevelChapter) "chapters as top-level" $
|
||||||
|
headers =?>
|
||||||
unlines [ "<chapter>"
|
unlines [ "<chapter>"
|
||||||
, " <title>header1</title>"
|
, " <title>header1</title>"
|
||||||
, " <sect1>"
|
, " <sect1>"
|
||||||
|
@ -266,7 +269,8 @@ tests = [ testGroup "line blocks"
|
||||||
, " </sect1>"
|
, " </sect1>"
|
||||||
, "</chapter>"
|
, "</chapter>"
|
||||||
]
|
]
|
||||||
, test (docbookTopLevelDiv Part) "parts as top-level" $ headers =?>
|
, test (docbookTopLevelDiv TopLevelPart) "parts as top-level" $
|
||||||
|
headers =?>
|
||||||
unlines [ "<part>"
|
unlines [ "<part>"
|
||||||
, " <title>header1</title>"
|
, " <title>header1</title>"
|
||||||
, " <chapter>"
|
, " <chapter>"
|
||||||
|
@ -279,6 +283,20 @@ tests = [ testGroup "line blocks"
|
||||||
, " </chapter>"
|
, " </chapter>"
|
||||||
, "</part>"
|
, "</part>"
|
||||||
]
|
]
|
||||||
|
, test (docbookTopLevelDiv TopLevelDefault) "default top-level" $
|
||||||
|
headers =?>
|
||||||
|
unlines [ "<sect1>"
|
||||||
|
, " <title>header1</title>"
|
||||||
|
, " <sect2>"
|
||||||
|
, " <title>header2</title>"
|
||||||
|
, " <sect3>"
|
||||||
|
, " <title>header3</title>"
|
||||||
|
, " <para>"
|
||||||
|
, " </para>"
|
||||||
|
, " </sect3>"
|
||||||
|
, " </sect2>"
|
||||||
|
, "</sect1>"
|
||||||
|
]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
|
@ -88,45 +88,64 @@ tests = [ testGroup "code blocks"
|
||||||
<> header 2 (text "header2")
|
<> header 2 (text "header2")
|
||||||
<> header 3 (text "header3")
|
<> header 3 (text "header3")
|
||||||
|
|
||||||
latexTopLevelDiv :: (ToPandoc a) => Division -> a -> String
|
latexTopLevelDiv :: (ToPandoc a) => TopLevelDivision -> a -> String
|
||||||
latexTopLevelDiv division =
|
latexTopLevelDiv division =
|
||||||
latexWithOpts def{ writerTopLevelDivision = Just division }
|
latexWithOpts def{ writerTopLevelDivision = division }
|
||||||
|
|
||||||
beamerTopLevelDiv :: (ToPandoc a) => Division -> a -> String
|
beamerTopLevelDiv :: (ToPandoc a)
|
||||||
|
=> TopLevelDivision -> a -> String
|
||||||
beamerTopLevelDiv division =
|
beamerTopLevelDiv division =
|
||||||
latexWithOpts def { writerTopLevelDivision = Just division
|
latexWithOpts def { writerTopLevelDivision = division
|
||||||
, writerBeamer = True }
|
, writerBeamer = True }
|
||||||
in
|
in
|
||||||
[ test (latexTopLevelDiv Section) "sections as top-level" $ headers =?>
|
[ test (latexTopLevelDiv TopLevelSection)
|
||||||
|
"sections as top-level" $ headers =?>
|
||||||
unlines [ "\\section{header1}\n"
|
unlines [ "\\section{header1}\n"
|
||||||
, "\\subsection{header2}\n"
|
, "\\subsection{header2}\n"
|
||||||
, "\\subsubsection{header3}"
|
, "\\subsubsection{header3}"
|
||||||
]
|
]
|
||||||
, test (latexTopLevelDiv Chapter) "chapters as top-level" $ headers =?>
|
, test (latexTopLevelDiv TopLevelChapter)
|
||||||
|
"chapters as top-level" $ headers =?>
|
||||||
unlines [ "\\chapter{header1}\n"
|
unlines [ "\\chapter{header1}\n"
|
||||||
, "\\section{header2}\n"
|
, "\\section{header2}\n"
|
||||||
, "\\subsection{header3}"
|
, "\\subsection{header3}"
|
||||||
]
|
]
|
||||||
, test (latexTopLevelDiv Part) "parts as top-level" $ headers =?>
|
, test (latexTopLevelDiv TopLevelPart)
|
||||||
|
"parts as top-level" $ headers =?>
|
||||||
unlines [ "\\part{header1}\n"
|
unlines [ "\\part{header1}\n"
|
||||||
, "\\chapter{header2}\n"
|
, "\\chapter{header2}\n"
|
||||||
, "\\section{header3}"
|
, "\\section{header3}"
|
||||||
]
|
]
|
||||||
, test (beamerTopLevelDiv Section) "sections as top-level in beamer" $ headers =?>
|
, test (latexTopLevelDiv TopLevelDefault)
|
||||||
|
"default top-level" $ headers =?>
|
||||||
unlines [ "\\section{header1}\n"
|
unlines [ "\\section{header1}\n"
|
||||||
, "\\subsection{header2}\n"
|
, "\\subsection{header2}\n"
|
||||||
, "\\subsubsection{header3}"
|
, "\\subsubsection{header3}"
|
||||||
]
|
]
|
||||||
, test (beamerTopLevelDiv Chapter) "chapters are as part in beamer" $ headers =?>
|
, test (beamerTopLevelDiv TopLevelSection)
|
||||||
|
"sections as top-level in beamer" $ headers =?>
|
||||||
|
unlines [ "\\section{header1}\n"
|
||||||
|
, "\\subsection{header2}\n"
|
||||||
|
, "\\subsubsection{header3}"
|
||||||
|
]
|
||||||
|
, test (beamerTopLevelDiv TopLevelChapter)
|
||||||
|
"chapters are as part in beamer" $ headers =?>
|
||||||
unlines [ "\\part{header1}\n"
|
unlines [ "\\part{header1}\n"
|
||||||
, "\\section{header2}\n"
|
, "\\section{header2}\n"
|
||||||
, "\\subsection{header3}"
|
, "\\subsection{header3}"
|
||||||
]
|
]
|
||||||
, test (beamerTopLevelDiv Part) "parts as top-level in beamer" $ headers =?>
|
, test (beamerTopLevelDiv TopLevelPart)
|
||||||
|
"parts as top-level in beamer" $ headers =?>
|
||||||
unlines [ "\\part{header1}\n"
|
unlines [ "\\part{header1}\n"
|
||||||
, "\\section{header2}\n"
|
, "\\section{header2}\n"
|
||||||
, "\\subsection{header3}"
|
, "\\subsection{header3}"
|
||||||
]
|
]
|
||||||
|
, test (beamerTopLevelDiv TopLevelDefault)
|
||||||
|
"default top-level in beamer" $ headers =?>
|
||||||
|
unlines [ "\\section{header1}\n"
|
||||||
|
, "\\subsection{header2}\n"
|
||||||
|
, "\\subsubsection{header3}"
|
||||||
|
]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
Loading…
Add table
Reference in a new issue