Merge pull request #3108 from tarleb/part
Add command line option allowing to set type of top-level divisions
This commit is contained in:
commit
1da40d63b1
9 changed files with 208 additions and 56 deletions
18
MANUAL.txt
18
MANUAL.txt
|
@ -661,11 +661,19 @@ Options affecting specific writers
|
||||||
|
|
||||||
`--chapters`
|
`--chapters`
|
||||||
|
|
||||||
: Treat top-level headers as chapters in LaTeX, ConTeXt, and DocBook
|
: Deprecated synonym for `--top-level-division=chapter`.
|
||||||
output. When the LaTeX document class is set to `report`, `book`,
|
|
||||||
or `memoir` (unless the `article` option is specified), this
|
`--top-level-division=[section|chapter|part]`
|
||||||
option is implied. If `beamer` is the output format, top-level
|
|
||||||
headers will become `\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`
|
`-N`, `--number-sections`
|
||||||
|
|
||||||
|
|
20
pandoc.hs
20
pandoc.hs
|
@ -183,7 +183,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
|
||||||
, optChapters :: Bool -- ^ Use chapter for top-level sects
|
, optTopLevelDivision :: Division -- ^ 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
|
||||||
|
@ -248,7 +248,7 @@ defaultOpts = Opt
|
||||||
, optHtmlQTags = False
|
, optHtmlQTags = False
|
||||||
, optHighlight = True
|
, optHighlight = True
|
||||||
, optHighlightStyle = pygments
|
, optHighlightStyle = pygments
|
||||||
, optChapters = False
|
, optTopLevelDivision = Section
|
||||||
, optHTMLMathMethod = PlainMath
|
, optHTMLMathMethod = PlainMath
|
||||||
, optReferenceODT = Nothing
|
, optReferenceODT = Nothing
|
||||||
, optReferenceDocx = Nothing
|
, optReferenceDocx = Nothing
|
||||||
|
@ -606,9 +606,19 @@ options =
|
||||||
|
|
||||||
, Option "" ["chapters"]
|
, Option "" ["chapters"]
|
||||||
(NoArg
|
(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"
|
"" -- "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 }
|
||||||
|
_ -> err 76 "could not parse top-level division")
|
||||||
|
"[section|chapter|part]")
|
||||||
|
"" -- "Use top-level division type in LaTeX, ConTeXt, DocBook"
|
||||||
|
|
||||||
, Option "N" ["number-sections"]
|
, Option "N" ["number-sections"]
|
||||||
(NoArg
|
(NoArg
|
||||||
(\opt -> return opt { optNumberSections = True }))
|
(\opt -> return opt { optNumberSections = True }))
|
||||||
|
@ -1122,7 +1132,7 @@ convertWithOpts opts args = do
|
||||||
, optHtmlQTags = htmlQTags
|
, optHtmlQTags = htmlQTags
|
||||||
, optHighlight = highlight
|
, optHighlight = highlight
|
||||||
, optHighlightStyle = highlightStyle
|
, optHighlightStyle = highlightStyle
|
||||||
, optChapters = chapters
|
, optTopLevelDivision = topLevelDivision
|
||||||
, optHTMLMathMethod = mathMethod'
|
, optHTMLMathMethod = mathMethod'
|
||||||
, optReferenceODT = referenceODT
|
, optReferenceODT = referenceODT
|
||||||
, optReferenceDocx = referenceDocx
|
, optReferenceDocx = referenceDocx
|
||||||
|
@ -1386,7 +1396,7 @@ convertWithOpts opts args = do
|
||||||
writerUserDataDir = datadir,
|
writerUserDataDir = datadir,
|
||||||
writerHtml5 = html5,
|
writerHtml5 = html5,
|
||||||
writerHtmlQTags = htmlQTags,
|
writerHtmlQTags = htmlQTags,
|
||||||
writerChapters = chapters,
|
writerTopLevelDivision = topLevelDivision,
|
||||||
writerListings = listings,
|
writerListings = listings,
|
||||||
writerBeamer = False,
|
writerBeamer = False,
|
||||||
writerSlideLevel = slideLevel,
|
writerSlideLevel = slideLevel,
|
||||||
|
|
|
@ -43,6 +43,7 @@ module Text.Pandoc.Options ( Extension(..)
|
||||||
, HTMLSlideVariant (..)
|
, HTMLSlideVariant (..)
|
||||||
, EPUBVersion (..)
|
, EPUBVersion (..)
|
||||||
, WrapOption (..)
|
, WrapOption (..)
|
||||||
|
, Division (..)
|
||||||
, WriterOptions (..)
|
, WriterOptions (..)
|
||||||
, TrackChanges (..)
|
, TrackChanges (..)
|
||||||
, ReferenceLocation (..)
|
, ReferenceLocation (..)
|
||||||
|
@ -337,6 +338,12 @@ data WrapOption = WrapAuto -- ^ Automatically wrap to width
|
||||||
| WrapPreserve -- ^ Preserve wrapping of input source
|
| WrapPreserve -- ^ Preserve wrapping of input source
|
||||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
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
|
-- | Locations for footnotes and references in markdown output
|
||||||
data ReferenceLocation = EndOfBlock -- ^ End of block
|
data ReferenceLocation = EndOfBlock -- ^ End of block
|
||||||
| EndOfSection -- ^ prior to next section header (or end of document)
|
| 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
|
, 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
|
||||||
, writerChapters :: Bool -- ^ Use "chapter" for top-level sects
|
, writerTopLevelDivision :: Division -- ^ 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
|
||||||
|
@ -421,7 +428,7 @@ instance Default WriterOptions where
|
||||||
, writerHtmlQTags = False
|
, writerHtmlQTags = False
|
||||||
, writerBeamer = False
|
, writerBeamer = False
|
||||||
, writerSlideLevel = Nothing
|
, writerSlideLevel = Nothing
|
||||||
, writerChapters = False
|
, writerTopLevelDivision = Section
|
||||||
, writerListings = False
|
, writerListings = False
|
||||||
, writerHighlight = False
|
, writerHighlight = False
|
||||||
, writerHighlightStyle = pygments
|
, writerHighlightStyle = pygments
|
||||||
|
|
|
@ -83,9 +83,10 @@ pandocToConTeXt options (Pandoc meta blocks) = do
|
||||||
]
|
]
|
||||||
let context = defField "toc" (writerTableOfContents options)
|
let context = defField "toc" (writerTableOfContents options)
|
||||||
$ defField "placelist" (intercalate ("," :: String) $
|
$ defField "placelist" (intercalate ("," :: String) $
|
||||||
take (writerTOCDepth options + if writerChapters options
|
take (writerTOCDepth options +
|
||||||
then 0
|
if writerTopLevelDivision options < Section
|
||||||
else 1)
|
then 0
|
||||||
|
else 1)
|
||||||
["chapter","section","subsection","subsubsection",
|
["chapter","section","subsection","subsubsection",
|
||||||
"subsubsubsection","subsubsubsubsection"])
|
"subsubsubsection","subsubsubsubsection"])
|
||||||
$ defField "body" main
|
$ defField "body" main
|
||||||
|
@ -412,7 +413,7 @@ inlineToConTeXt (Span (_,_,kvs) ils) = do
|
||||||
Nothing -> txt
|
Nothing -> txt
|
||||||
fmap (wrapLang . wrapDir) $ inlineListToConTeXt ils
|
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
|
sectionHeader :: Attr
|
||||||
-> Int
|
-> Int
|
||||||
-> [Inline]
|
-> [Inline]
|
||||||
|
@ -421,21 +422,26 @@ 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' = 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 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")
|
||||||
else (text "section", text "chapter")
|
else (text "section", text "chapter")
|
||||||
return $ if level' >= 1 && level' <= 5
|
return $ case level' of
|
||||||
then char '\\'
|
-1 -> text "\\part" <> braces contents
|
||||||
<> text (concat (replicate (level' - 1) "sub"))
|
0 -> char '\\' <> chapter <> braces contents
|
||||||
<> section
|
n | n >= 1 && n <= 5 -> char '\\'
|
||||||
<> (if (not . null) ident' then brackets (text ident') else empty)
|
<> text (concat (replicate (n - 1) "sub"))
|
||||||
<> braces contents
|
<> section
|
||||||
<> blankline
|
<> (if (not . null) ident'
|
||||||
else if level' == 0
|
then brackets (text ident')
|
||||||
then char '\\' <> chapter <> braces contents
|
else empty)
|
||||||
else contents <> blankline
|
<> braces contents
|
||||||
|
<> blankline
|
||||||
|
_ -> contents <> blankline
|
||||||
|
|
||||||
fromBcp47' :: String -> String
|
fromBcp47' :: String -> String
|
||||||
fromBcp47' = fromBcp47 . splitBy (=='-')
|
fromBcp47' = fromBcp47 . splitBy (=='-')
|
||||||
|
|
|
@ -79,12 +79,16 @@ writeDocbook opts (Pandoc meta blocks) =
|
||||||
colwidth = if writerWrapText opts == WrapAuto
|
colwidth = if writerWrapText opts == WrapAuto
|
||||||
then Just $ writerColumns opts
|
then Just $ writerColumns opts
|
||||||
else Nothing
|
else Nothing
|
||||||
render' = render colwidth
|
render' = render colwidth
|
||||||
opts' = if "/book>" `isSuffixOf`
|
opts' = if ("/book>" `isSuffixOf` (trimr $ writerTemplate opts) &&
|
||||||
(trimr $ writerTemplate opts)
|
writerTopLevelDivision opts >= Section)
|
||||||
then opts{ writerChapters = True }
|
then opts{ writerTopLevelDivision = Chapter }
|
||||||
else opts
|
else opts
|
||||||
startLvl = if writerChapters opts' then 0 else 1
|
-- 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
|
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
|
||||||
|
@ -111,11 +115,12 @@ elementToDocbook opts lvl (Sec _ _num (id',_,_) title elements) =
|
||||||
then [Blk (Para [])]
|
then [Blk (Para [])]
|
||||||
else elements
|
else elements
|
||||||
tag = case lvl of
|
tag = case lvl of
|
||||||
n | n == 0 -> "chapter"
|
-1 -> "part"
|
||||||
| n >= 1 && n <= 5 -> if writerDocbook5 opts
|
0 -> "chapter"
|
||||||
|
n | n >= 1 && n <= 5 -> if writerDocbook5 opts
|
||||||
then "section"
|
then "section"
|
||||||
else "sect" ++ show n
|
else "sect" ++ show n
|
||||||
| otherwise -> "simplesect"
|
_ -> "simplesect"
|
||||||
idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')]
|
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")]
|
nsAttr = if writerDocbook5 opts && lvl == 0 then [("xmlns", "http://docbook.org/ns/docbook"),("xmlns:xlink", "http://www.w3.org/1999/xlink")]
|
||||||
else []
|
else []
|
||||||
|
|
|
@ -87,7 +87,8 @@ writeLaTeX options document =
|
||||||
stOptions = options, stVerbInNote = False,
|
stOptions = options, stVerbInNote = False,
|
||||||
stTable = False, stStrikeout = False,
|
stTable = False, stStrikeout = False,
|
||||||
stUrl = False, stGraphics = False,
|
stUrl = False, stGraphics = False,
|
||||||
stLHS = False, stBook = writerChapters options,
|
stLHS = False,
|
||||||
|
stBook = writerTopLevelDivision options < Section,
|
||||||
stCsquotes = False, stHighlighting = False,
|
stCsquotes = False, stHighlighting = False,
|
||||||
stIncremental = writerIncremental options,
|
stIncremental = writerIncremental options,
|
||||||
stInternalLinks = [], stUsesEuro = False }
|
stInternalLinks = [], stUsesEuro = False }
|
||||||
|
@ -750,10 +751,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 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
|
let sectionType = case level' of
|
||||||
0 | writerBeamer opts -> "part"
|
-1 -> "part"
|
||||||
| otherwise -> "chapter"
|
0 -> "chapter"
|
||||||
1 -> "section"
|
1 -> "section"
|
||||||
2 -> "subsection"
|
2 -> "subsection"
|
||||||
3 -> "subsubsection"
|
3 -> "subsubsection"
|
||||||
|
|
|
@ -35,7 +35,7 @@ import Text.Pandoc.Shared
|
||||||
import Text.Pandoc.Writers.Shared
|
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, isSuffixOf )
|
import Data.List ( stripPrefix, isPrefixOf )
|
||||||
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
|
||||||
|
@ -60,19 +60,18 @@ writeTEI opts (Pandoc meta blocks) =
|
||||||
then Just $ writerColumns opts
|
then Just $ writerColumns opts
|
||||||
else Nothing
|
else Nothing
|
||||||
render' = render colwidth
|
render' = render colwidth
|
||||||
opts' = if "/book>" `isSuffixOf`
|
startLvl = case writerTopLevelDivision opts of
|
||||||
(trimr $ writerTemplate opts)
|
Part -> -1
|
||||||
then opts{ writerChapters = True }
|
Chapter -> 0
|
||||||
else opts
|
Section -> 1
|
||||||
startLvl = if writerChapters opts' then 0 else 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
|
||||||
(Just . render colwidth . (vcat .
|
(Just . render colwidth . (vcat .
|
||||||
(map (elementToTEI opts' startLvl)) . hierarchicalize))
|
(map (elementToTEI opts startLvl)) . hierarchicalize))
|
||||||
(Just . render colwidth . inlinesToTEI opts')
|
(Just . render colwidth . inlinesToTEI opts)
|
||||||
meta'
|
meta'
|
||||||
main = render' $ vcat (map (elementToTEI opts' startLvl) elements)
|
main = render' $ vcat (map (elementToTEI opts startLvl) elements)
|
||||||
context = defField "body" main
|
context = defField "body" main
|
||||||
$ defField "mathml" (case writerHTMLMathMethod opts of
|
$ defField "mathml" (case writerHTMLMathMethod opts of
|
||||||
MathML _ -> True
|
MathML _ -> True
|
||||||
|
@ -90,8 +89,10 @@ elementToTEI opts lvl (Sec _ _num (id',_,_) title elements) =
|
||||||
let elements' = if null elements
|
let elements' = if null elements
|
||||||
then [Blk (Para [])]
|
then [Blk (Para [])]
|
||||||
else elements
|
else elements
|
||||||
|
-- level numbering correspond to LaTeX internals
|
||||||
divType = case lvl of
|
divType = case lvl of
|
||||||
n | n == 0 -> "chapter"
|
n | n == -1 -> "part"
|
||||||
|
| n == 0 -> "chapter"
|
||||||
| n >= 1 && n <= 5 -> "level" ++ show n
|
| n >= 1 && n <= 5 -> "level" ++ show n
|
||||||
| otherwise -> "section"
|
| otherwise -> "section"
|
||||||
in inTags True "div" [("type", divType) | not (null id')] $
|
in inTags True "div" [("type", divType) | not (null id')] $
|
||||||
|
|
|
@ -8,7 +8,10 @@ import Tests.Helpers
|
||||||
import Text.Pandoc.Arbitrary()
|
import Text.Pandoc.Arbitrary()
|
||||||
|
|
||||||
docbook :: (ToPandoc a) => a -> String
|
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
|
"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>"
|
||||||
|
]
|
||||||
|
]
|
||||||
|
]
|
||||||
]
|
]
|
||||||
|
|
|
@ -2,16 +2,19 @@
|
||||||
module Tests.Writers.LaTeX (tests) where
|
module Tests.Writers.LaTeX (tests) where
|
||||||
|
|
||||||
import Test.Framework
|
import Test.Framework
|
||||||
import Text.Pandoc.Builder
|
|
||||||
import Text.Pandoc
|
|
||||||
import Tests.Helpers
|
import Tests.Helpers
|
||||||
import Text.Pandoc.Arbitrary()
|
import Text.Pandoc
|
||||||
|
import Text.Pandoc.Arbitrary ()
|
||||||
|
import Text.Pandoc.Builder
|
||||||
|
|
||||||
latex :: (ToPandoc a) => a -> String
|
latex :: (ToPandoc a) => a -> String
|
||||||
latex = writeLaTeX def{ writerHighlight = True } . toPandoc
|
latex = latexWithOpts def{ writerHighlight = True }
|
||||||
|
|
||||||
latexListing :: (ToPandoc a) => a -> String
|
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
|
"my test" =: X =?> Y
|
||||||
|
@ -78,4 +81,52 @@ tests = [ testGroup "code blocks"
|
||||||
, "backtick" =:
|
, "backtick" =:
|
||||||
code "`nu?`" =?> "\\texttt{\\textasciigrave{}nu?\\textasciigrave{}}"
|
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}"
|
||||||
|
]
|
||||||
|
]
|
||||||
|
]
|
||||||
]
|
]
|
||||||
|
|
Loading…
Add table
Reference in a new issue