Use template variables for include-before/after.
* These options now imply -s; previously they worked also in fragment mode. * Users can now adjust position of include-before and include-after text in the templates. * Default position of include-before moved back (as it originally was) before table of contents. * Resolves Issue #217. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1883 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
a35af5db29
commit
3b9be92492
26 changed files with 113 additions and 69 deletions
10
README
10
README
|
@ -276,14 +276,14 @@ For further documentation, see the `pandoc(1)` man page.
|
|||
`\begin{document}` command in LaTeX). This can be used to include
|
||||
navigation bars or banners in HTML documents. This option can be
|
||||
used repeatedly to include multiple files. They will be included in
|
||||
the order specified.
|
||||
the order specified. Implies `--standalone`.
|
||||
|
||||
`-A` or `--include-after-body` *filename*
|
||||
: includes the contents of *filename* (verbatim) at the end of
|
||||
the document body (before the `</body>` tag in HTML, or the
|
||||
`\end{document}` command in LaTeX). This option can be be used
|
||||
repeatedly to include multiple files. They will be included in the
|
||||
order specified.
|
||||
order specified. Implies `--standalone`.
|
||||
|
||||
`--reference-odt` *filename*
|
||||
: uses the specified file as a style reference in producing an ODT.
|
||||
|
@ -475,6 +475,12 @@ depending on the output format, but include:
|
|||
values)
|
||||
`toc`
|
||||
: non-null value if `--toc/--table-of-contents` was specified
|
||||
`include-before`
|
||||
: contents specified by `-B/--include-before-body` (may have
|
||||
multiple values)
|
||||
`include-after`
|
||||
: contents specified by `-A/--include-after-body` (may have
|
||||
multiple values)
|
||||
`body`
|
||||
: body of document
|
||||
`title`
|
||||
|
|
|
@ -195,9 +195,11 @@ should pipe input and output through `iconv`:
|
|||
|
||||
-B *FILE*, \--include-before-body=*FILE*
|
||||
: Include contents of *FILE* at the beginning of the document body.
|
||||
Implies `-s`.
|
||||
|
||||
-A *FILE*, \--include-after-body=*FILE*
|
||||
: Include contents of *FILE* at the end of the document body.
|
||||
Implies `-s`.
|
||||
|
||||
-C *FILE*, \--custom-header=*FILE*
|
||||
: Use contents of *FILE* as the document header. *Note: This option is
|
||||
|
@ -295,6 +297,12 @@ depending on the output format, but include:
|
|||
values)
|
||||
`toc`
|
||||
: non-null value if `--toc/--table-of-contents` was specified
|
||||
`include-before`
|
||||
: contents specified by `-B/--include-before-body` (may have
|
||||
multiple values)
|
||||
`include-after`
|
||||
: contents specified by `-A/--include-after-body` (may have
|
||||
multiple values)
|
||||
`body`
|
||||
: body of document
|
||||
`title`
|
||||
|
|
|
@ -64,13 +64,7 @@ pandocToConTeXt options (Pandoc (Meta title authors date) blocks) = do
|
|||
then return ""
|
||||
else liftM render $ inlineListToConTeXt date
|
||||
body <- blockListToConTeXt blocks
|
||||
let before = if null (writerIncludeBefore options)
|
||||
then empty
|
||||
else text $ writerIncludeBefore options
|
||||
let after = if null (writerIncludeAfter options)
|
||||
then empty
|
||||
else text $ writerIncludeAfter options
|
||||
let main = render $ before $$ body $$ after
|
||||
let main = render body
|
||||
let context = writerVariables options ++
|
||||
[ ("toc", if writerTableOfContents options then "yes" else "")
|
||||
, ("body", main)
|
||||
|
|
|
@ -65,12 +65,7 @@ writeDocbook opts (Pandoc (Meta tit auths dat) blocks) =
|
|||
authors = map (authorToDocbook opts) auths
|
||||
date = inlinesToDocbook opts dat
|
||||
elements = hierarchicalize blocks
|
||||
before = writerIncludeBefore opts
|
||||
after = writerIncludeAfter opts
|
||||
main = render $
|
||||
(if null before then empty else text before) $$
|
||||
vcat (map (elementToDocbook opts) elements) $$
|
||||
(if null after then empty else text after)
|
||||
main = render $ vcat (map (elementToDocbook opts) elements)
|
||||
context = writerVariables opts ++
|
||||
[ ("body", main)
|
||||
, ("title", render title)
|
||||
|
|
|
@ -105,9 +105,7 @@ pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do
|
|||
blocks' <- liftM toHtmlFromList $ mapM (elementToHtml opts) sects
|
||||
st <- get
|
||||
let notes = reverse (stNotes st)
|
||||
let before = primHtml $ writerIncludeBefore opts
|
||||
let after = primHtml $ writerIncludeAfter opts
|
||||
let thebody = before +++ blocks' +++ footnoteSection notes +++ after
|
||||
let thebody = blocks' +++ footnoteSection notes
|
||||
let math = if stMath st
|
||||
then case writerHTMLMathMethod opts of
|
||||
LaTeXMathML (Just url) ->
|
||||
|
|
|
@ -74,13 +74,7 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
|
|||
authorsText <- mapM (liftM render . inlineListToLaTeX) authors
|
||||
dateText <- liftM render $ inlineListToLaTeX date
|
||||
body <- blockListToLaTeX blocks
|
||||
let before = if null (writerIncludeBefore options)
|
||||
then empty
|
||||
else text $ writerIncludeBefore options
|
||||
let after = if null (writerIncludeAfter options)
|
||||
then empty
|
||||
else text $ writerIncludeAfter options
|
||||
let main = render $ before $$ body $$ after
|
||||
let main = render body
|
||||
st <- get
|
||||
let context = writerVariables options ++
|
||||
[ ("toc", if writerTableOfContents options then "yes" else "")
|
||||
|
|
|
@ -48,10 +48,6 @@ writeMan opts document = evalState (pandocToMan opts document) (WriterState [] F
|
|||
-- | Return groff man representation of document.
|
||||
pandocToMan :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToMan opts (Pandoc (Meta title authors date) blocks) = do
|
||||
let before = writerIncludeBefore opts
|
||||
let after = writerIncludeAfter opts
|
||||
let before' = if null before then empty else text before
|
||||
let after' = if null after then empty else text after
|
||||
titleText <- inlineListToMan opts title
|
||||
authors' <- mapM (inlineListToMan opts) authors
|
||||
date' <- inlineListToMan opts date
|
||||
|
@ -66,7 +62,7 @@ pandocToMan opts (Pandoc (Meta title authors date) blocks) = do
|
|||
body <- blockListToMan opts blocks
|
||||
notes <- liftM stNotes get
|
||||
notes' <- notesToMan opts (reverse notes)
|
||||
let main = render $ before' $$ body $$ notes' $$ after'
|
||||
let main = render $ body $$ notes'
|
||||
hasTables <- liftM stHasTables get
|
||||
let context = writerVariables opts ++
|
||||
[ ("body", main)
|
||||
|
|
|
@ -60,17 +60,11 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do
|
|||
then tableOfContents opts headerBlocks
|
||||
else empty
|
||||
body <- blockListToMarkdown opts blocks
|
||||
let before = if null (writerIncludeBefore opts)
|
||||
then empty
|
||||
else text $ writerIncludeBefore opts
|
||||
let after = if null (writerIncludeAfter opts)
|
||||
then empty
|
||||
else text $ writerIncludeAfter opts
|
||||
(notes, _) <- get
|
||||
notes' <- notesToMarkdown opts (reverse notes)
|
||||
(_, refs) <- get -- note that the notes may contain refs
|
||||
refs' <- keyTableToMarkdown opts (reverse refs)
|
||||
let main = render $ before $+$ body $+$ text "" $+$ notes' $+$ text "" $+$ refs' $+$ after
|
||||
let main = render $ body $+$ text "" $+$ notes' $+$ text "" $+$ refs'
|
||||
let context = writerVariables opts ++
|
||||
[ ("toc", render toc)
|
||||
, ("body", main)
|
||||
|
|
|
@ -53,14 +53,12 @@ writeMediaWiki opts document =
|
|||
-- | Return MediaWiki representation of document.
|
||||
pandocToMediaWiki :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToMediaWiki opts (Pandoc _ blocks) = do
|
||||
let before = writerIncludeBefore opts
|
||||
let after = writerIncludeAfter opts
|
||||
body <- blockListToMediaWiki opts blocks
|
||||
notesExist <- get >>= return . stNotes
|
||||
let notes = if notesExist
|
||||
then "\n<references />"
|
||||
else ""
|
||||
let main = before ++ body ++ after ++ notes
|
||||
let main = body ++ notes
|
||||
let context = writerVariables opts ++
|
||||
[ ("body", main) ] ++
|
||||
[ ("toc", "yes") | writerTableOfContents opts ]
|
||||
|
|
|
@ -166,12 +166,7 @@ writeOpenDocument opts (Pandoc (Meta title authors date) blocks) =
|
|||
date'' <- inlinesToOpenDocument opts date
|
||||
doc'' <- blocksToOpenDocument opts blocks
|
||||
return (doc'', title'', authors'', date'')
|
||||
before = writerIncludeBefore opts
|
||||
after = writerIncludeAfter opts
|
||||
body = (if null before then empty else text before) $$
|
||||
doc $$
|
||||
(if null after then empty else text after)
|
||||
body' = render body
|
||||
body' = render doc
|
||||
styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s
|
||||
listStyle (n,l) = inTags True "text:list-style"
|
||||
[("style:name", "L" ++ show n)] (vcat l)
|
||||
|
|
|
@ -59,10 +59,6 @@ writeRST opts document =
|
|||
pandocToRST :: Pandoc -> State WriterState String
|
||||
pandocToRST (Pandoc (Meta tit auth dat) blocks) = do
|
||||
opts <- liftM stOptions get
|
||||
let before = writerIncludeBefore opts
|
||||
after = writerIncludeAfter opts
|
||||
before' = if null before then empty else text before
|
||||
after' = if null after then empty else text after
|
||||
title <- titleToRST tit
|
||||
authors <- mapM inlineListToRST auth
|
||||
date <- inlineListToRST dat
|
||||
|
@ -72,8 +68,7 @@ pandocToRST (Pandoc (Meta tit auth dat) blocks) = do
|
|||
refs <- liftM (reverse . stLinks) get >>= keyTableToRST
|
||||
pics <- liftM (reverse . stImages) get >>= pictTableToRST
|
||||
hasMath <- liftM stHasMath get
|
||||
let main = render $ before' $+$ body $+$ notes $+$
|
||||
text "" $+$ refs $+$ pics $+$ after'
|
||||
let main = render $ body $+$ notes $+$ text "" $+$ refs $+$ pics
|
||||
let context = writerVariables opts ++
|
||||
[ ("body", main)
|
||||
, ("title", render title)
|
||||
|
|
|
@ -42,9 +42,7 @@ writeRTF options (Pandoc (Meta title authors date) blocks) =
|
|||
authorstext = map inlineListToRTF authors
|
||||
datetext = inlineListToRTF date
|
||||
spacer = not $ all null $ titletext : datetext : authorstext
|
||||
body = writerIncludeBefore options ++
|
||||
concatMap (blockToRTF 0 AlignDefault) blocks ++
|
||||
writerIncludeAfter options
|
||||
body = concatMap (blockToRTF 0 AlignDefault) blocks
|
||||
context = writerVariables options ++
|
||||
[ ("body", body)
|
||||
, ("title", titletext)
|
||||
|
|
|
@ -69,13 +69,7 @@ pandocToTexinfo options (Pandoc (Meta title authors date) blocks) = do
|
|||
let titlePage = not $ all null $ title : date : authors
|
||||
main <- blockListToTexinfo blocks
|
||||
st <- get
|
||||
let before = if null (writerIncludeBefore options)
|
||||
then empty
|
||||
else text (writerIncludeBefore options)
|
||||
let after = if null (writerIncludeAfter options)
|
||||
then empty
|
||||
else text (writerIncludeAfter options)
|
||||
let body = render $ before $$ main $$ after
|
||||
let body = render main
|
||||
let context = writerVariables options ++
|
||||
[ ("body", body)
|
||||
, ("title", render titleText)
|
||||
|
|
|
@ -399,9 +399,10 @@ options =
|
|||
(ReqArg
|
||||
(\arg opt -> do
|
||||
text <- readFile arg
|
||||
let oldBefore = optBefore opt
|
||||
-- add new text to end, so it is included in proper order
|
||||
return opt { optBefore = oldBefore ++ [text] })
|
||||
-- add new ones to end, so they're included in order specified
|
||||
let newvars = optVariables opt ++ [("include-before",text)]
|
||||
return opt { optVariables = newvars,
|
||||
optStandalone = True })
|
||||
"FILENAME")
|
||||
"" -- "File to include before document body"
|
||||
|
||||
|
@ -409,9 +410,10 @@ options =
|
|||
(ReqArg
|
||||
(\arg opt -> do
|
||||
text <- readFile arg
|
||||
let oldAfter = optAfter opt
|
||||
-- add new text to end, so it is included in proper order
|
||||
return opt { optAfter = oldAfter ++ [text]})
|
||||
-- add new ones to end, so they're included in order specified
|
||||
let newvars = optVariables opt ++ [("include-after",text)]
|
||||
return opt { optVariables = newvars,
|
||||
optStandalone = True })
|
||||
"FILENAME")
|
||||
"" -- "File to include after document body"
|
||||
|
||||
|
|
|
@ -73,10 +73,16 @@ $endif$
|
|||
\blank[3*medium]
|
||||
\stopalignment
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
\placecontent
|
||||
$endif$
|
||||
|
||||
$body$
|
||||
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
||||
\stoptext
|
||||
|
|
|
@ -17,6 +17,12 @@ $if(date)$
|
|||
<date>$date$</date>
|
||||
$endif$
|
||||
</articleinfo>
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
||||
</article>
|
||||
|
||||
|
|
|
@ -44,9 +44,15 @@ $endif$
|
|||
$if(title)$
|
||||
<h1 class="title">$title$</h1>
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
$toc$
|
||||
$endif$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
||||
</body>
|
||||
</html>
|
||||
|
|
|
@ -80,10 +80,18 @@ $if(title)$
|
|||
\maketitle
|
||||
$endif$
|
||||
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
\tableofcontents
|
||||
|
||||
$endif$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
|
||||
$include-after$
|
||||
$endfor$
|
||||
|
||||
\end{document}
|
||||
|
|
|
@ -5,7 +5,13 @@ $endif$
|
|||
$for(header-includes)$
|
||||
$header-includes$
|
||||
$endfor$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
||||
$if(author)$
|
||||
.SH AUTHORS
|
||||
$for(author)$$author$$sep$; $endfor$.
|
||||
|
|
|
@ -7,9 +7,17 @@ $endif$
|
|||
$for(header-includes)$
|
||||
$header-includes$
|
||||
|
||||
$endfor$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
$toc$
|
||||
|
||||
$endif$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
|
||||
$include-after$
|
||||
$endfor$
|
||||
|
|
|
@ -1,8 +1,16 @@
|
|||
$if(legacy-header)$
|
||||
$legacy-header$
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
__TOC__
|
||||
|
||||
$endif$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
|
||||
$include-after$
|
||||
$endfor$
|
||||
|
|
|
@ -15,7 +15,13 @@ $endfor$
|
|||
$if(date)$
|
||||
<text:p text:style-name="Date">$date$</text:p>
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
||||
</office:text>
|
||||
</office:body>
|
||||
</office:document-content>
|
||||
|
|
|
@ -20,6 +20,10 @@ $if(math)$
|
|||
:format: html latex
|
||||
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
.. contents::
|
||||
|
||||
|
@ -29,3 +33,7 @@ $header-includes$
|
|||
|
||||
$endfor$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
|
||||
$include-after$
|
||||
$endfor$
|
||||
|
|
|
@ -21,5 +21,11 @@ $endif$
|
|||
$if(spacer)$
|
||||
{\pard \ql \f0 \sa180 \li0 \fi0 \par}
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
$endfor$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
$include-after$
|
||||
$endfor$
|
||||
}
|
||||
|
|
|
@ -51,10 +51,18 @@ $endif$
|
|||
@end titlepage
|
||||
|
||||
$endif$
|
||||
$for(include-before)$
|
||||
$include-before$
|
||||
|
||||
$endfor$
|
||||
$if(toc)$
|
||||
@contents
|
||||
|
||||
$endif$
|
||||
$body$
|
||||
$for(include-after)$
|
||||
|
||||
$include-after$
|
||||
$endfor$
|
||||
|
||||
@bye
|
||||
|
|
|
@ -57,7 +57,8 @@ STUFF INSERTED
|
|||
></li
|
||||
></ul
|
||||
></div
|
||||
>STUFF INSERTED
|
||||
>
|
||||
STUFF INSERTED
|
||||
</body>
|
||||
</html>
|
||||
|
||||
|
|
Loading…
Add table
Reference in a new issue