Added --base-header-level option.

Thanks to Jérémy Bobbio for the patch that formed the basis of this commit.
Closes Debian #563416.

git-svn-id: https://pandoc.googlecode.com/svn/trunk@1889 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2010-03-14 23:23:26 +00:00
parent 075f958c6a
commit baae74af57
3 changed files with 34 additions and 6 deletions

3
README
View file

@ -243,6 +243,9 @@ For further documentation, see the `pandoc(1)` man page.
one) in the output document. This option has no effect with `man`, one) in the output document. This option has no effect with `man`,
`docbook`, or `s5` output formats. `docbook`, or `s5` output formats.
`--base-header-level` *level*
: specifies the base level for headers (defaults to 1).
`--template=`*file* `--template=`*file*
: uses *file* as a custom template for the generated document. Implies : uses *file* as a custom template for the generated document. Implies
`-s`. See [Templates](#templates) below for a description `-s`. See [Templates](#templates) below for a description

View file

@ -174,6 +174,9 @@ should pipe input and output through `iconv`:
RTF) or an instruction to create one (LaTeX, reStructuredText). RTF) or an instruction to create one (LaTeX, reStructuredText).
This option has no effect on man, DocBook, or S5 output. This option has no effect on man, DocBook, or S5 output.
\--base-header-level=*LEVEL*
: Specify the base level for headers (defaults to 1).
\--template=*FILE* \--template=*FILE*
: Use *FILE* as a custom template for the generated document. Implies : Use *FILE* as a custom template for the generated document. Implies
`-s`. See TEMPLATES below for a description of template syntax. If `-s`. See TEMPLATES below for a description of template syntax. If

View file

@ -42,7 +42,7 @@ import System.Exit ( exitWith, ExitCode (..) )
import System.FilePath import System.FilePath
import System.Console.GetOpt import System.Console.GetOpt
import Data.Maybe ( fromMaybe ) import Data.Maybe ( fromMaybe )
import Data.Char ( toLower ) import Data.Char ( toLower, isDigit )
import Data.List ( intercalate, isSuffixOf ) import Data.List ( intercalate, isSuffixOf )
import System.Directory ( getAppUserDataDirectory ) import System.Directory ( getAppUserDataDirectory )
import System.IO ( stdout, stderr ) import System.IO ( stdout, stderr )
@ -59,7 +59,7 @@ import Text.CSL
import Text.Pandoc.Biblio import Text.Pandoc.Biblio
#endif #endif
import Control.Monad (when, unless, liftM) import Control.Monad (when, unless, liftM)
import Network.HTTP import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
import Network.URI (parseURI) import Network.URI (parseURI)
import Data.ByteString.Lazy.UTF8 (toString) import Data.ByteString.Lazy.UTF8 (toString)
@ -145,6 +145,7 @@ data Opt = Opt
, optWriter :: String -- ^ Writer format , optWriter :: String -- ^ Writer format
, optParseRaw :: Bool -- ^ Parse unconvertable HTML and TeX , optParseRaw :: Bool -- ^ Parse unconvertable HTML and TeX
, optTableOfContents :: Bool -- ^ Include table of contents , optTableOfContents :: Bool -- ^ Include table of contents
, optHeaderShift :: Int -- ^ Headers base level
, optTemplate :: String -- ^ Custom template , optTemplate :: String -- ^ Custom template
, optVariables :: [(String,String)] -- ^ Template variables to set , optVariables :: [(String,String)] -- ^ Template variables to set
, optBefore :: [String] -- ^ Texts to include before body , optBefore :: [String] -- ^ Texts to include before body
@ -184,6 +185,7 @@ defaultOpts = Opt
, optWriter = "" -- null for default writer , optWriter = "" -- null for default writer
, optParseRaw = False , optParseRaw = False
, optTableOfContents = False , optTableOfContents = False
, optHeaderShift = 1
, optTemplate = "" , optTemplate = ""
, optVariables = [] , optVariables = []
, optBefore = [] , optBefore = []
@ -352,6 +354,17 @@ options =
(\opt -> return opt { optTableOfContents = True })) (\opt -> return opt { optTableOfContents = True }))
"" -- "Include table of contents" "" -- "Include table of contents"
, Option "" ["base-header-level"]
(ReqArg
(\arg opt -> do
if all isDigit arg && (read arg :: Int) >= 1
then return opt { optHeaderShift = read arg - 1 }
else do
hPutStrLn stderr $ "base-header-level must be a number >= 1"
exitWith $ ExitFailure 19)
"LEVEL")
"" -- "Headers base level"
, Option "" ["template"] , Option "" ["template"]
(ReqArg (ReqArg
(\arg opt -> do (\arg opt -> do
@ -559,6 +572,10 @@ defaultWriterName x =
['.',y] | y `elem` ['1'..'9'] -> "man" ['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html" _ -> "html"
shiftHeaderLevels :: Int -> Block -> Block
shiftHeaderLevels shift (Header level inner) = Header (level + shift) inner
shiftHeaderLevels _ x = x
main :: IO () main :: IO ()
main = do main = do
@ -595,6 +612,7 @@ main = do
, optBefore = befores , optBefore = befores
, optAfter = afters , optAfter = afters
, optTableOfContents = toc , optTableOfContents = toc
, optHeaderShift = headerShift
, optTemplate = template , optTemplate = template
, optOutputFile = outputFile , optOutputFile = outputFile
, optNumberSections = numberSections , optNumberSections = numberSections
@ -748,14 +766,18 @@ main = do
doc <- fmap (reader startParserState . convertTabs . intercalate "\n") (readSources sources) doc <- fmap (reader startParserState . convertTabs . intercalate "\n") (readSources sources)
doc' <- do let doc' = if headerShift > 1
then processWith (shiftHeaderLevels headerShift) doc
else doc
doc'' <- do
#ifdef _CITEPROC #ifdef _CITEPROC
processBiblio cslFile refs doc processBiblio cslFile refs doc'
#else #else
return doc return doc'
#endif #endif
let writerOutput = writer writerOptions doc' ++ "\n" let writerOutput = writer writerOptions doc'' ++ "\n"
case writerName' of case writerName' of
"odt" -> saveOpenDocumentAsODT datadir outputFile sourceDirRelative referenceODT writerOutput "odt" -> saveOpenDocumentAsODT datadir outputFile sourceDirRelative referenceODT writerOutput