Implemented templates for context writer.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1701 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
1f580fb701
commit
b7750b705a
2 changed files with 43 additions and 76 deletions
|
@ -35,6 +35,7 @@ import Data.List ( isSuffixOf, intercalate, intersperse )
|
|||
import Control.Monad.State
|
||||
import Control.Monad (liftM)
|
||||
import Text.PrettyPrint.HughesPJ hiding ( Str )
|
||||
import Text.Pandoc.Templates ( renderTemplate )
|
||||
|
||||
data WriterState =
|
||||
WriterState { stNextRef :: Int -- number of next URL reference
|
||||
|
@ -52,54 +53,34 @@ writeConTeXt options document =
|
|||
, stOrderedListLevel = 0
|
||||
, stOptions = options
|
||||
}
|
||||
in render $
|
||||
evalState (pandocToConTeXt options document) defaultWriterState
|
||||
in evalState (pandocToConTeXt options document) defaultWriterState
|
||||
|
||||
pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState Doc
|
||||
pandocToConTeXt options (Pandoc meta blocks) = do
|
||||
return empty -- TODO
|
||||
-- main <- 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 body = before $$ main $$ after
|
||||
-- head' <- if writerStandalone options
|
||||
-- then contextHeader options meta
|
||||
-- else return empty
|
||||
-- let toc = if writerTableOfContents options
|
||||
-- then text "\\placecontent\n"
|
||||
-- else empty
|
||||
-- let foot = if writerStandalone options
|
||||
-- then text "\\stoptext\n"
|
||||
-- else empty
|
||||
-- return $ head' $$ toc $$ body $$ foot
|
||||
|
||||
-- | Insert bibliographic information into ConTeXt header.
|
||||
contextHeader :: WriterOptions -- ^ Options, including ConTeXt header
|
||||
-> Meta -- ^ Meta with bibliographic information
|
||||
-> State WriterState Doc
|
||||
contextHeader options (Meta title authors date) = do
|
||||
return empty -- TODO
|
||||
-- titletext <- if null title
|
||||
-- then return empty
|
||||
-- else inlineListToConTeXt title
|
||||
-- let authorstext = if null authors
|
||||
-- then ""
|
||||
-- else if length authors == 1
|
||||
-- then stringToConTeXt $ head authors
|
||||
-- else stringToConTeXt $ (intercalate ", " $
|
||||
-- init authors) ++ " & " ++ last authors
|
||||
-- let datetext = if date == ""
|
||||
-- then ""
|
||||
-- else stringToConTeXt date
|
||||
-- let titleblock = text "\\doctitle{" <> titletext <> char '}' $$
|
||||
-- text ("\\author{" ++ authorstext ++ "}") $$
|
||||
-- text ("\\date{" ++ datetext ++ "}")
|
||||
-- let header = text $ writerHeader options
|
||||
-- return $ header $$ titleblock $$ text "\\starttext\n\\maketitle\n"
|
||||
pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToConTeXt options (Pandoc (Meta title authors date) blocks) = do
|
||||
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
|
||||
titletext <- if null title
|
||||
then return ""
|
||||
else liftM render $ inlineListToConTeXt title
|
||||
authorstext <- mapM (liftM render . inlineListToConTeXt) authors
|
||||
datetext <- if null date
|
||||
then return ""
|
||||
else liftM render $ inlineListToConTeXt date
|
||||
let context = writerVariables options ++
|
||||
[ ("toc", if writerTableOfContents options then "yes" else "")
|
||||
, ("body", main)
|
||||
, ("title", titletext)
|
||||
, ("authors", intercalate "\\\\" authorstext)
|
||||
, ("date", datetext) ]
|
||||
return $ if writerStandalone options
|
||||
then renderTemplate context $ writerTemplate options
|
||||
else main
|
||||
|
||||
-- escape things as needed for ConTeXt
|
||||
|
||||
|
|
|
@ -1,3 +1,6 @@
|
|||
$if(legacy-header)$
|
||||
$legacy-header$
|
||||
$else$
|
||||
\enableregime[utf] % use UTF-8
|
||||
|
||||
\setupcolors[state=start]
|
||||
|
@ -67,43 +70,26 @@ after={\blank[medium]},
|
|||
]
|
||||
|
||||
\protect
|
||||
|
||||
$endif$
|
||||
$header-includes$
|
||||
|
||||
$if(title)$
|
||||
\doctitle{$title$}
|
||||
\author{\$authors\$}
|
||||
\date{\$date\$}
|
||||
$endif$
|
||||
$if(authors)$
|
||||
\author{$authors$}
|
||||
$endif$
|
||||
$if(date)$
|
||||
\date{$date$}
|
||||
$endif$
|
||||
\starttext
|
||||
\maketitle
|
||||
|
||||
$if(toc)$
|
||||
\placecontent
|
||||
$endif$
|
||||
|
||||
\subject{section oen}
|
||||
|
||||
\startitemize[n][stopper=.]
|
||||
\item
|
||||
one
|
||||
\startitemize[a][stopper=.]
|
||||
\item
|
||||
two
|
||||
\startitemize[r][start=3,stopper=.,width=2.5em]
|
||||
\item
|
||||
three
|
||||
\stopitemize
|
||||
\stopitemize
|
||||
\stopitemize
|
||||
|
||||
\starttyping
|
||||
hi
|
||||
\stoptyping
|
||||
|
||||
footnote
|
||||
\footnote{with code
|
||||
|
||||
\starttyping
|
||||
code
|
||||
\stoptyping
|
||||
}
|
||||
$body$
|
||||
|
||||
\stoptext
|
||||
|
||||
|
|
Loading…
Add table
Reference in a new issue