Removed unneeded writer options; use template variables instead.

Removed writerIncludeAfter, writerIncludeBefore, writerTitlePrefix,
writerHeader.  Removed corresponding fields of Options structure
in pandoc.hs.  The options now set template variables (writerVariables)
instead.

git-svn-id: https://pandoc.googlecode.com/svn/trunk@1684 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2009-12-31 01:10:17 +00:00
parent c602ed3459
commit 9f126c15cf
13 changed files with 289 additions and 288 deletions

View file

@ -982,8 +982,6 @@ data WriterOptions = WriterOptions
{ writerStandalone :: Bool -- ^ Include header and footer { writerStandalone :: Bool -- ^ Include header and footer
, writerTemplate :: String -- ^ Template to use in standalone mode , writerTemplate :: String -- ^ Template to use in standalone mode
, writerVariables :: [(String, String)] -- ^ Variables to set in template , writerVariables :: [(String, String)] -- ^ Variables to set in template
, writerHeader :: String -- ^ Header for the document
, writerTitlePrefix :: String -- ^ Prefix for HTML titles
, writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs , writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs
, writerTableOfContents :: Bool -- ^ Include table of contents , writerTableOfContents :: Bool -- ^ Include table of contents
, writerS5 :: Bool -- ^ We're writing S5 , writerS5 :: Bool -- ^ We're writing S5
@ -991,8 +989,6 @@ data WriterOptions = WriterOptions
, writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc) , writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc)
, writerIncremental :: Bool -- ^ Incremental S5 lists , writerIncremental :: Bool -- ^ Incremental S5 lists
, writerNumberSections :: Bool -- ^ Number sections in LaTeX , writerNumberSections :: Bool -- ^ Number sections in LaTeX
, writerIncludeBefore :: String -- ^ String to include before the body
, writerIncludeAfter :: String -- ^ String to include after the body
, writerStrictMarkdown :: Bool -- ^ Use strict markdown syntax , writerStrictMarkdown :: Bool -- ^ Use strict markdown syntax
, writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
, writerWrapText :: Bool -- ^ Wrap text to line length , writerWrapText :: Bool -- ^ Wrap text to line length
@ -1007,8 +1003,6 @@ defaultWriterOptions =
WriterOptions { writerStandalone = False WriterOptions { writerStandalone = False
, writerTemplate = "" , writerTemplate = ""
, writerVariables = [] , writerVariables = []
, writerHeader = ""
, writerTitlePrefix = ""
, writerTabStop = 4 , writerTabStop = 4
, writerTableOfContents = False , writerTableOfContents = False
, writerS5 = False , writerS5 = False
@ -1016,8 +1010,6 @@ defaultWriterOptions =
, writerIgnoreNotes = False , writerIgnoreNotes = False
, writerIncremental = False , writerIncremental = False
, writerNumberSections = False , writerNumberSections = False
, writerIncludeBefore = ""
, writerIncludeAfter = ""
, writerStrictMarkdown = False , writerStrictMarkdown = False
, writerReferenceLinks = False , writerReferenceLinks = False
, writerWrapText = True , writerWrapText = True

View file

@ -57,47 +57,49 @@ writeConTeXt options document =
pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState Doc pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState Doc
pandocToConTeXt options (Pandoc meta blocks) = do pandocToConTeXt options (Pandoc meta blocks) = do
main <- blockListToConTeXt blocks return empty -- TODO
let before = if null (writerIncludeBefore options) -- main <- blockListToConTeXt blocks
then empty -- let before = if null (writerIncludeBefore options)
else text $ writerIncludeBefore options -- then empty
let after = if null (writerIncludeAfter options) -- else text $ writerIncludeBefore options
then empty -- let after = if null (writerIncludeAfter options)
else text $ writerIncludeAfter options -- then empty
let body = before $$ main $$ after -- else text $ writerIncludeAfter options
head' <- if writerStandalone options -- let body = before $$ main $$ after
then contextHeader options meta -- head' <- if writerStandalone options
else return empty -- then contextHeader options meta
let toc = if writerTableOfContents options -- else return empty
then text "\\placecontent\n" -- let toc = if writerTableOfContents options
else empty -- then text "\\placecontent\n"
let foot = if writerStandalone options -- else empty
then text "\\stoptext\n" -- let foot = if writerStandalone options
else empty -- then text "\\stoptext\n"
return $ head' $$ toc $$ body $$ foot -- else empty
-- return $ head' $$ toc $$ body $$ foot
-- | Insert bibliographic information into ConTeXt header. -- | Insert bibliographic information into ConTeXt header.
contextHeader :: WriterOptions -- ^ Options, including ConTeXt header contextHeader :: WriterOptions -- ^ Options, including ConTeXt header
-> Meta -- ^ Meta with bibliographic information -> Meta -- ^ Meta with bibliographic information
-> State WriterState Doc -> State WriterState Doc
contextHeader options (Meta title authors date) = do contextHeader options (Meta title authors date) = do
titletext <- if null title return empty -- TODO
then return empty -- titletext <- if null title
else inlineListToConTeXt title -- then return empty
let authorstext = if null authors -- else inlineListToConTeXt title
then "" -- let authorstext = if null authors
else if length authors == 1 -- then ""
then stringToConTeXt $ head authors -- else if length authors == 1
else stringToConTeXt $ (intercalate ", " $ -- then stringToConTeXt $ head authors
init authors) ++ " & " ++ last authors -- else stringToConTeXt $ (intercalate ", " $
let datetext = if date == "" -- init authors) ++ " & " ++ last authors
then "" -- let datetext = if date == ""
else stringToConTeXt date -- then ""
let titleblock = text "\\doctitle{" <> titletext <> char '}' $$ -- else stringToConTeXt date
text ("\\author{" ++ authorstext ++ "}") $$ -- let titleblock = text "\\doctitle{" <> titletext <> char '}' $$
text ("\\date{" ++ datetext ++ "}") -- text ("\\author{" ++ authorstext ++ "}") $$
let header = text $ writerHeader options -- text ("\\date{" ++ datetext ++ "}")
return $ header $$ titleblock $$ text "\\starttext\n\\maketitle\n" -- let header = text $ writerHeader options
-- return $ header $$ titleblock $$ text "\\starttext\n\\maketitle\n"
-- escape things as needed for ConTeXt -- escape things as needed for ConTeXt

View file

@ -59,25 +59,26 @@ authorToDocbook name = inTagsIndented "author" $
-- | Convert Pandoc document to string in Docbook format. -- | Convert Pandoc document to string in Docbook format.
writeDocbook :: WriterOptions -> Pandoc -> String writeDocbook :: WriterOptions -> Pandoc -> String
writeDocbook opts (Pandoc (Meta title authors date) blocks) = writeDocbook opts (Pandoc (Meta title authors date) blocks) =
let head' = if writerStandalone opts "" -- TODO
then text (writerHeader opts) -- let head' = if writerStandalone opts
else empty -- then text (writerHeader opts)
meta = if writerStandalone opts -- else empty
then inTagsIndented "articleinfo" $ -- meta = if writerStandalone opts
(inTagsSimple "title" (wrap opts title)) $$ -- then inTagsIndented "articleinfo" $
(vcat (map authorToDocbook authors)) $$ -- (inTagsSimple "title" (wrap opts title)) $$
(inTagsSimple "date" (text $ escapeStringForXML date)) -- (vcat (map authorToDocbook authors)) $$
else empty -- (inTagsSimple "date" (text $ escapeStringForXML date))
elements = hierarchicalize blocks -- else empty
before = writerIncludeBefore opts -- elements = hierarchicalize blocks
after = writerIncludeAfter opts -- before = writerIncludeBefore opts
body = (if null before then empty else text before) $$ -- after = writerIncludeAfter opts
vcat (map (elementToDocbook opts) elements) $$ -- body = (if null before then empty else text before) $$
(if null after then empty else text after) -- vcat (map (elementToDocbook opts) elements) $$
body' = if writerStandalone opts -- (if null after then empty else text after)
then inTagsIndented "article" (meta $$ body) -- body' = if writerStandalone opts
else body -- then inTagsIndented "article" (meta $$ body)
in render $ head' $$ body' $$ text "" -- else body
-- in render $ head' $$ body' $$ text ""
-- | Convert an Element to Docbook. -- | Convert an Element to Docbook.
elementToDocbook :: WriterOptions -> Element -> Doc elementToDocbook :: WriterOptions -> Element -> Doc

View file

@ -88,63 +88,64 @@ writeHtmlString opts =
-- | Convert Pandoc document to Html structure. -- | Convert Pandoc document to Html structure.
writeHtml :: WriterOptions -> Pandoc -> Html writeHtml :: WriterOptions -> Pandoc -> Html
writeHtml opts (Pandoc (Meta tit authors date) blocks) = writeHtml opts (Pandoc (Meta tit authors date) blocks) =
let titlePrefix = writerTitlePrefix opts noHtml -- TODO
(topTitle,st) = runState (inlineListToHtml opts tit) defaultWriterState -- let titlePrefix = writerTitlePrefix opts
topTitle'' = stripTags $ showHtmlFragment topTitle -- (topTitle,st) = runState (inlineListToHtml opts tit) defaultWriterState
topTitle' = titlePrefix ++ -- topTitle'' = stripTags $ showHtmlFragment topTitle
(if null topTitle'' || null titlePrefix -- topTitle' = titlePrefix ++
then "" -- (if null topTitle'' || null titlePrefix
else " - ") ++ topTitle'' -- then ""
metadata = thetitle << topTitle' +++ -- else " - ") ++ topTitle''
meta ! [httpequiv "Content-Type", -- metadata = thetitle << topTitle' +++
content "text/html; charset=UTF-8"] +++ -- meta ! [httpequiv "Content-Type",
meta ! [name "generator", content "pandoc"] +++ -- content "text/html; charset=UTF-8"] +++
(toHtmlFromList $ -- meta ! [name "generator", content "pandoc"] +++
map (\a -> meta ! [name "author", content a]) authors) +++ -- (toHtmlFromList $
(if null date -- map (\a -> meta ! [name "author", content a]) authors) +++
then noHtml -- (if null date
else meta ! [name "date", content date]) -- then noHtml
titleHeader = if writerStandalone opts && not (null tit) && -- else meta ! [name "date", content date])
not (writerS5 opts) -- titleHeader = if writerStandalone opts && not (null tit) &&
then h1 ! [theclass "title"] $ topTitle -- not (writerS5 opts)
else noHtml -- then h1 ! [theclass "title"] $ topTitle
sects = hierarchicalize blocks -- else noHtml
toc = if writerTableOfContents opts -- sects = hierarchicalize blocks
then evalState (tableOfContents opts sects) st -- toc = if writerTableOfContents opts
else noHtml -- then evalState (tableOfContents opts sects) st
(blocks', st') = runState -- else noHtml
(mapM (elementToHtml opts) sects >>= return . toHtmlFromList) -- (blocks', st') = runState
st -- (mapM (elementToHtml opts) sects >>= return . toHtmlFromList)
cssLines = stCSS st' -- st
css = if S.null cssLines -- cssLines = stCSS st'
then noHtml -- css = if S.null cssLines
else style ! [thetype "text/css"] $ primHtml $ -- then noHtml
'\n':(unlines $ S.toList cssLines) -- else style ! [thetype "text/css"] $ primHtml $
math = if stMath st' -- '\n':(unlines $ S.toList cssLines)
then case writerHTMLMathMethod opts of -- math = if stMath st'
LaTeXMathML Nothing -> -- then case writerHTMLMathMethod opts of
primHtml latexMathMLScript -- LaTeXMathML Nothing ->
LaTeXMathML (Just url) -> -- primHtml latexMathMLScript
script ! -- LaTeXMathML (Just url) ->
[src url, thetype "text/javascript"] $ -- script !
noHtml -- [src url, thetype "text/javascript"] $
JsMath (Just url) -> -- noHtml
script ! -- JsMath (Just url) ->
[src url, thetype "text/javascript"] $ -- script !
noHtml -- [src url, thetype "text/javascript"] $
_ -> noHtml -- noHtml
else noHtml -- _ -> noHtml
head' = header $ metadata +++ math +++ css +++ -- else noHtml
primHtml (renderTemplate [] $ writerHeader opts) -- head' = header $ metadata +++ math +++ css +++
notes = reverse (stNotes st') -- primHtml (renderTemplate [] $ writerHeader opts)
before = primHtml $ writerIncludeBefore opts -- notes = reverse (stNotes st')
after = primHtml $ writerIncludeAfter opts -- before = primHtml $ writerIncludeBefore opts
thebody = before +++ titleHeader +++ toc +++ blocks' +++ -- after = primHtml $ writerIncludeAfter opts
footnoteSection notes +++ after -- thebody = before +++ titleHeader +++ toc +++ blocks' +++
in if writerStandalone opts -- footnoteSection notes +++ after
then head' +++ body thebody -- in if writerStandalone opts
else thebody -- then head' +++ body thebody
-- else thebody
-- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix -- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix
prefixedId :: WriterOptions -> String -> HtmlAttr prefixedId :: WriterOptions -> String -> HtmlAttr

View file

@ -57,15 +57,13 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
then return "" then return ""
else liftM render $ inlineListToLaTeX title else liftM render $ inlineListToLaTeX title
let context = writerVariables options ++ let context = writerVariables options ++
[ ("before", writerIncludeBefore options) [ ("toc", if writerTableOfContents options then "yes" else "")
, ("after", writerIncludeAfter options)
, ("toc", if writerTableOfContents options then "yes" else "")
, ("body", main) , ("body", main)
, ("title", titletext) , ("title", titletext)
, ("authors", intercalate "\\\\" $ map stringToLaTeX authors) , ("authors", intercalate "\\\\" $ map stringToLaTeX authors)
, ("date", stringToLaTeX date) ] , ("date", stringToLaTeX date) ]
let templ = if writerStandalone options let templ = if writerStandalone options
then writerHeader options then writerTemplate options
else "$if(toc)$\\tableofcontents\n$endif$" ++ else "$if(toc)$\\tableofcontents\n$endif$" ++
"$if(before)$$before$\n$endif$" ++ "$if(before)$$before$\n$endif$" ++
"$body$$if(after)$$after$\n$endif$" "$body$$if(after)$$after$\n$endif$"

View file

@ -48,18 +48,19 @@ writeMan opts document = render $ evalState (pandocToMan opts document) ([],[])
-- | Return groff man representation of document. -- | Return groff man representation of document.
pandocToMan :: WriterOptions -> Pandoc -> State WriterState Doc pandocToMan :: WriterOptions -> Pandoc -> State WriterState Doc
pandocToMan opts (Pandoc meta blocks) = do pandocToMan opts (Pandoc meta blocks) = do
let before = writerIncludeBefore opts return empty -- TODO
let after = writerIncludeAfter opts -- let before = writerIncludeBefore opts
let before' = if null before then empty else text before -- let after = writerIncludeAfter opts
let after' = if null after then empty else text after -- let before' = if null before then empty else text before
(head', foot) <- metaToMan opts meta -- let after' = if null after then empty else text after
body <- blockListToMan opts blocks -- (head', foot) <- metaToMan opts meta
(notes, preprocessors) <- get -- body <- blockListToMan opts blocks
let preamble = if null preprocessors || not (writerStandalone opts) -- (notes, preprocessors) <- get
then empty -- let preamble = if null preprocessors || not (writerStandalone opts)
else text $ ".\\\" " ++ concat (nub preprocessors) -- then empty
notes' <- notesToMan opts (reverse notes) -- else text $ ".\\\" " ++ concat (nub preprocessors)
return $ preamble $$ head' $$ before' $$ body $$ notes' $$ foot $$ after' -- notes' <- notesToMan opts (reverse notes)
-- return $ preamble $$ head' $$ before' $$ body $$ notes' $$ foot $$ after'
-- | Insert bibliographic information into Man header and footer. -- | Insert bibliographic information into Man header and footer.
metaToMan :: WriterOptions -- ^ Options, including Man header metaToMan :: WriterOptions -- ^ Options, including Man header

View file

@ -50,27 +50,28 @@ writeMarkdown opts document =
-- | Return markdown representation of document. -- | Return markdown representation of document.
pandocToMarkdown :: WriterOptions -> Pandoc -> State WriterState Doc pandocToMarkdown :: WriterOptions -> Pandoc -> State WriterState Doc
pandocToMarkdown opts (Pandoc meta blocks) = do pandocToMarkdown opts (Pandoc meta blocks) = do
let before = writerIncludeBefore opts return empty -- TODO
let after = writerIncludeAfter opts -- let before = writerIncludeBefore opts
let header = writerHeader opts -- let after = writerIncludeAfter opts
let before' = if null before then empty else text before -- let header = writerHeader opts
let after' = if null after then empty else text after -- let before' = if null before then empty else text before
let header' = if null header then empty else text header -- let after' = if null after then empty else text after
metaBlock <- metaToMarkdown opts meta -- let header' = if null header then empty else text header
let head' = if writerStandalone opts -- metaBlock <- metaToMarkdown opts meta
then metaBlock $+$ header' -- let head' = if writerStandalone opts
else empty -- then metaBlock $+$ header'
let headerBlocks = filter isHeaderBlock blocks -- else empty
let toc = if writerTableOfContents opts -- let headerBlocks = filter isHeaderBlock blocks
then tableOfContents opts headerBlocks -- let toc = if writerTableOfContents opts
else empty -- then tableOfContents opts headerBlocks
body <- blockListToMarkdown opts blocks -- else empty
(notes, _) <- get -- body <- blockListToMarkdown opts blocks
notes' <- notesToMarkdown opts (reverse notes) -- (notes, _) <- get
(_, refs) <- get -- note that the notes may contain refs -- notes' <- notesToMarkdown opts (reverse notes)
refs' <- keyTableToMarkdown opts (reverse refs) -- (_, refs) <- get -- note that the notes may contain refs
return $ head' $+$ before' $+$ toc $+$ body $+$ text "" $+$ -- refs' <- keyTableToMarkdown opts (reverse refs)
notes' $+$ text "" $+$ refs' $+$ after' -- return $ head' $+$ before' $+$ toc $+$ body $+$ text "" $+$
-- notes' $+$ text "" $+$ refs' $+$ after'
-- | Return markdown representation of reference key table. -- | Return markdown representation of reference key table.
keyTableToMarkdown :: WriterOptions -> KeyTable -> State WriterState Doc keyTableToMarkdown :: WriterOptions -> KeyTable -> State WriterState Doc

View file

@ -52,20 +52,21 @@ writeMediaWiki opts document =
-- | Return MediaWiki representation of document. -- | Return MediaWiki representation of document.
pandocToMediaWiki :: WriterOptions -> Pandoc -> State WriterState String pandocToMediaWiki :: WriterOptions -> Pandoc -> State WriterState String
pandocToMediaWiki opts (Pandoc _ blocks) = do pandocToMediaWiki opts (Pandoc _ blocks) = do
let before = writerIncludeBefore opts return "" -- TODO
let after = writerIncludeAfter opts -- let before = writerIncludeBefore opts
let head' = if writerStandalone opts -- let after = writerIncludeAfter opts
then writerHeader opts -- let head' = if writerStandalone opts
else "" -- then writerHeader opts
let toc = if writerTableOfContents opts -- else ""
then "__TOC__\n" -- let toc = if writerTableOfContents opts
else "" -- then "__TOC__\n"
body <- blockListToMediaWiki opts blocks -- else ""
notesExist <- get >>= return . stNotes -- body <- blockListToMediaWiki opts blocks
let notes = if notesExist -- notesExist <- get >>= return . stNotes
then "\n== Notes ==\n<references />" -- let notes = if notesExist
else "" -- then "\n== Notes ==\n<references />"
return $ head' ++ before ++ toc ++ body ++ after ++ notes -- else ""
-- return $ head' ++ before ++ toc ++ body ++ after ++ notes
-- | Escape special characters for MediaWiki. -- | Escape special characters for MediaWiki.
escapeString :: String -> String escapeString :: String -> String

View file

@ -180,28 +180,29 @@ authorToOpenDocument name =
-- | Convert Pandoc document to string in OpenDocument format. -- | Convert Pandoc document to string in OpenDocument format.
writeOpenDocument :: WriterOptions -> Pandoc -> String writeOpenDocument :: WriterOptions -> Pandoc -> String
writeOpenDocument opts (Pandoc (Meta title authors date) blocks) = writeOpenDocument opts (Pandoc (Meta title authors date) blocks) =
let root = inTags True "office:document-content" openDocumentNameSpaces "" -- TODO
header = when (writerStandalone opts) $ text (writerHeader opts) -- let root = inTags True "office:document-content" openDocumentNameSpaces
title' = case runState (wrap opts title) defaultWriterState of -- header = when (writerStandalone opts) $ text (writerHeader opts)
(t,_) -> if isEmpty t then empty else inHeaderTags 1 t -- title' = case runState (wrap opts title) defaultWriterState of
authors' = when (authors /= []) $ vcat (map authorToOpenDocument authors) -- (t,_) -> if isEmpty t then empty else inHeaderTags 1 t
date' = when (date /= []) $ -- authors' = when (authors /= []) $ vcat (map authorToOpenDocument authors)
inParagraphTagsWithStyle "Date" (text $ escapeStringForXML date) -- date' = when (date /= []) $
meta = when (writerStandalone opts) $ title' $$ authors' $$ date' -- inParagraphTagsWithStyle "Date" (text $ escapeStringForXML date)
before = writerIncludeBefore opts -- meta = when (writerStandalone opts) $ title' $$ authors' $$ date'
after = writerIncludeAfter opts -- before = writerIncludeBefore opts
(doc, s) = runState (blocksToOpenDocument opts blocks) defaultWriterState -- after = writerIncludeAfter opts
body = (if null before then empty else text before) $$ -- (doc, s) = runState (blocksToOpenDocument opts blocks) defaultWriterState
doc $$ -- body = (if null before then empty else text before) $$
(if null after then empty else text after) -- doc $$
body' = if writerStandalone opts -- (if null after then empty else text after)
then inTagsIndented "office:body" $ -- body' = if writerStandalone opts
inTagsIndented "office:text" (meta $$ body) -- then inTagsIndented "office:body" $
else body -- inTagsIndented "office:text" (meta $$ body)
styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s -- else body
listStyle (n,l) = inTags True "text:list-style" [("style:name", "L" ++ show n)] (vcat l) -- styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s
listStyles = map listStyle (stListStyles s) -- listStyle (n,l) = inTags True "text:list-style" [("style:name", "L" ++ show n)] (vcat l)
in render $ header $$ root (generateStyles (styles ++ listStyles) $$ body' $$ text "") -- listStyles = map listStyle (stListStyles s)
-- in render $ header $$ root (generateStyles (styles ++ listStyles) $$ body' $$ text "")
withParagraphStyle :: WriterOptions -> String -> [Block] -> State WriterState Doc withParagraphStyle :: WriterOptions -> String -> [Block] -> State WriterState Doc
withParagraphStyle o s (b:bs) withParagraphStyle o s (b:bs)

View file

@ -57,26 +57,27 @@ writeRST opts document =
-- | Return RST representation of document. -- | Return RST representation of document.
pandocToRST :: Pandoc -> State WriterState Doc pandocToRST :: Pandoc -> State WriterState Doc
pandocToRST (Pandoc meta blocks) = do pandocToRST (Pandoc meta blocks) = do
opts <- get >>= (return . stOptions) return empty -- TODO
let before = writerIncludeBefore opts -- opts <- get >>= (return . stOptions)
after = writerIncludeAfter opts -- let before = writerIncludeBefore opts
header = writerHeader opts -- after = writerIncludeAfter opts
before' = if null before then empty else text before -- header = writerHeader opts
after' = if null after then empty else text after -- before' = if null before then empty else text before
header' = if null header then empty else text header -- after' = if null after then empty else text after
metaBlock <- metaToRST opts meta -- header' = if null header then empty else text header
let head' = if (writerStandalone opts) -- metaBlock <- metaToRST opts meta
then metaBlock $+$ header' -- let head' = if (writerStandalone opts)
else empty -- then metaBlock $+$ header'
body <- blockListToRST blocks -- else empty
includes <- get >>= (return . concat . stIncludes) -- body <- blockListToRST blocks
let includes' = if null includes then empty else text includes -- includes <- get >>= (return . concat . stIncludes)
notes <- get >>= (notesToRST . reverse . stNotes) -- let includes' = if null includes then empty else text includes
-- note that the notes may contain refs, so we do them first -- notes <- get >>= (notesToRST . reverse . stNotes)
refs <- get >>= (keyTableToRST . reverse . stLinks) -- -- note that the notes may contain refs, so we do them first
pics <- get >>= (pictTableToRST . reverse . stImages) -- refs <- get >>= (keyTableToRST . reverse . stLinks)
return $ head' $+$ before' $+$ includes' $+$ body $+$ notes $+$ text "" $+$ -- pics <- get >>= (pictTableToRST . reverse . stImages)
refs $+$ pics $+$ after' -- return $ head' $+$ before' $+$ includes' $+$ body $+$ notes $+$ text "" $+$
-- refs $+$ pics $+$ after'
-- | Return RST representation of reference key table. -- | Return RST representation of reference key table.
keyTableToRST :: KeyTable -> State WriterState Doc keyTableToRST :: KeyTable -> State WriterState Doc

View file

@ -37,17 +37,18 @@ import Data.Char ( ord, isDigit )
-- | Convert Pandoc to a string in rich text format. -- | Convert Pandoc to a string in rich text format.
writeRTF :: WriterOptions -> Pandoc -> String writeRTF :: WriterOptions -> Pandoc -> String
writeRTF options (Pandoc meta blocks) = writeRTF options (Pandoc meta blocks) =
let head' = if writerStandalone options "" -- TODO
then rtfHeader (writerHeader options) meta -- let head' = if writerStandalone options
else "" -- then rtfHeader (writerHeader options) meta
toc = if writerTableOfContents options -- else ""
then tableOfContents $ filter isHeaderBlock blocks -- toc = if writerTableOfContents options
else "" -- then tableOfContents $ filter isHeaderBlock blocks
foot = if writerStandalone options then "\n}\n" else "" -- else ""
body = writerIncludeBefore options ++ -- foot = if writerStandalone options then "\n}\n" else ""
concatMap (blockToRTF 0 AlignDefault) blocks ++ -- body = writerIncludeBefore options ++
writerIncludeAfter options -- concatMap (blockToRTF 0 AlignDefault) blocks ++
in head' ++ toc ++ body ++ foot -- writerIncludeAfter options
-- in head' ++ toc ++ body ++ foot
-- | Construct table of contents from list of header blocks. -- | Construct table of contents from list of header blocks.
tableOfContents :: [Block] -> String tableOfContents :: [Block] -> String

View file

@ -68,56 +68,58 @@ wrapTop (Pandoc (Meta title authors date) blocks) =
pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState Doc pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState Doc
pandocToTexinfo options (Pandoc meta blocks) = do pandocToTexinfo options (Pandoc meta blocks) = do
main <- blockListToTexinfo blocks return empty -- TODO
head' <- if writerStandalone options -- main <- blockListToTexinfo blocks
then texinfoHeader options meta -- head' <- if writerStandalone options
else return empty -- then texinfoHeader options meta
let before = if null (writerIncludeBefore options) -- else return empty
then empty -- let before = if null (writerIncludeBefore options)
else text (writerIncludeBefore options) -- then empty
let after = if null (writerIncludeAfter options) -- else text (writerIncludeBefore options)
then empty -- let after = if null (writerIncludeAfter options)
else text (writerIncludeAfter options) -- then empty
let body = before $$ main $$ after -- else text (writerIncludeAfter options)
-- XXX toc untested -- let body = before $$ main $$ after
let toc = if writerTableOfContents options -- -- XXX toc untested
then text "@contents" -- let toc = if writerTableOfContents options
else empty -- then text "@contents"
let foot = if writerStandalone options -- else empty
then text "@bye" -- let foot = if writerStandalone options
else empty -- then text "@bye"
return $ head' $$ toc $$ body $$ foot -- else empty
-- return $ head' $$ toc $$ body $$ foot
-- | Insert bibliographic information into Texinfo header. -- | Insert bibliographic information into Texinfo header.
texinfoHeader :: WriterOptions -- ^ Options, including Texinfo header texinfoHeader :: WriterOptions -- ^ Options, including Texinfo header
-> Meta -- ^ Meta with bibliographic information -> Meta -- ^ Meta with bibliographic information
-> State WriterState Doc -> State WriterState Doc
texinfoHeader options (Meta title authors date) = do texinfoHeader options (Meta title authors date) = do
titletext <- if null title return empty -- TODO
then return empty -- titletext <- if null title
else do -- then return empty
t <- inlineListToTexinfo title -- else do
return $ text "@title " <> t -- t <- inlineListToTexinfo title
headerIncludes <- get >>= return . S.toList . stIncludes -- return $ text "@title " <> t
let extras = text $ unlines headerIncludes -- headerIncludes <- get >>= return . S.toList . stIncludes
let authorstext = map makeAuthor authors -- let extras = text $ unlines headerIncludes
let datetext = if date == "" -- let authorstext = map makeAuthor authors
then empty -- let datetext = if date == ""
else text $ stringToTexinfo date -- then empty
-- else text $ stringToTexinfo date
let baseHeader = case writerHeader options of --
"" -> empty -- let baseHeader = case writerHeader options of
x -> text x -- "" -> empty
let header = text "@documentencoding utf-8" $$ baseHeader $$ extras -- x -> text x
return $ text "\\input texinfo" $$ -- let header = text "@documentencoding utf-8" $$ baseHeader $$ extras
header $$ -- return $ text "\\input texinfo" $$
text "@ifnottex" $$ -- header $$
text "@paragraphindent 0" $$ -- text "@ifnottex" $$
text "@end ifnottex" $$ -- text "@paragraphindent 0" $$
text "@titlepage" $$ -- text "@end ifnottex" $$
titletext $$ vcat authorstext $$ -- text "@titlepage" $$
datetext $$ -- titletext $$ vcat authorstext $$
text "@end titlepage" -- datetext $$
-- text "@end titlepage"
makeAuthor :: String -> Doc makeAuthor :: String -> Doc
makeAuthor author = text $ "@author " ++ (stringToTexinfo author) makeAuthor author = text $ "@author " ++ (stringToTexinfo author)

View file

@ -138,9 +138,6 @@ data Opt = Opt
, optTemplate :: String -- ^ Custom template , optTemplate :: String -- ^ Custom template
, optVariables :: [(String,String)] -- ^ Template variables to set , optVariables :: [(String,String)] -- ^ Template variables to set
, optIncludeInHeader :: String -- ^ File to include in header , optIncludeInHeader :: String -- ^ File to include in header
, optIncludeBeforeBody :: String -- ^ File to include at top of body
, optIncludeAfterBody :: String -- ^ File to include at end of body
, optTitlePrefix :: String -- ^ Optional prefix for HTML title
, optOutputFile :: String -- ^ Name of output file , optOutputFile :: String -- ^ Name of output file
, optNumberSections :: Bool -- ^ Number sections in LaTeX , optNumberSections :: Bool -- ^ Number sections in LaTeX
, optIncremental :: Bool -- ^ Use incremental lists in S5 , optIncremental :: Bool -- ^ Use incremental lists in S5
@ -177,9 +174,6 @@ defaultOpts = Opt
, optTemplate = "" , optTemplate = ""
, optVariables = [] , optVariables = []
, optIncludeInHeader = "" , optIncludeInHeader = ""
, optIncludeBeforeBody = ""
, optIncludeAfterBody = ""
, optTitlePrefix = ""
, optOutputFile = "-" -- "-" means stdout , optOutputFile = "-" -- "-" means stdout
, optNumberSections = False , optNumberSections = False
, optIncremental = False , optIncremental = False
@ -367,18 +361,28 @@ options =
, Option "B" ["include-before-body"] , Option "B" ["include-before-body"]
(ReqArg (ReqArg
(\arg opt -> do (\arg opt -> do
let old = optIncludeBeforeBody opt
text <- readFile arg text <- readFile arg
return opt { optIncludeBeforeBody = old ++ text }) let oldvars = optVariables opt
let newvars = case lookup "before" oldvars of
Nothing -> ("before", text) : oldvars
Just b -> ("before", b ++ text) :
filter ((/= "before") . fst)
oldvars
return opt { optVariables = newvars })
"FILENAME") "FILENAME")
"" -- "File to include before document body" "" -- "File to include before document body"
, Option "A" ["include-after-body"] , Option "A" ["include-after-body"]
(ReqArg (ReqArg
(\arg opt -> do (\arg opt -> do
let old = optIncludeAfterBody opt
text <- readFile arg text <- readFile arg
return opt { optIncludeAfterBody = old ++ text }) let oldvars = optVariables opt
let newvars = case lookup "after" oldvars of
Nothing -> ("after", text) : oldvars
Just a -> ("after", a ++ text) :
filter ((/= "after") . fst)
oldvars
return opt { optVariables = newvars })
"FILENAME") "FILENAME")
"" -- "File to include after document body" "" -- "File to include after document body"
@ -397,8 +401,10 @@ options =
, Option "T" ["title-prefix"] , Option "T" ["title-prefix"]
(ReqArg (ReqArg
(\arg opt -> return opt { optTitlePrefix = arg, (\arg opt -> do
optStandalone = True }) let newvars = ("title-prefix", arg) : optVariables opt
return opt { optVariables = newvars,
optStandalone = True })
"STRING") "STRING")
"" -- "String to prefix to HTML window title" "" -- "String to prefix to HTML window title"
@ -549,9 +555,6 @@ main = do
, optTableOfContents = toc , optTableOfContents = toc
, optTemplate = template , optTemplate = template
, optIncludeInHeader = includeHeader , optIncludeInHeader = includeHeader
, optIncludeBeforeBody = includeBefore
, optIncludeAfterBody = includeAfter
, optTitlePrefix = titlePrefix
, optOutputFile = outputFile , optOutputFile = outputFile
, optNumberSections = numberSections , optNumberSections = numberSections
, optIncremental = incremental , optIncremental = incremental
@ -633,12 +636,10 @@ main = do
[("header-includes", includeHeader)] ++ [("header-includes", includeHeader)] ++
variables variables
let writerOptions = WriterOptions { writerStandalone = standalone', let writerOptions = WriterOptions { writerStandalone = standalone',
writerTemplate = defaultTemplate, writerTemplate = if null template
writerVariables = variables',
writerHeader = if null template
then defaultTemplate then defaultTemplate
else template, else template,
writerTitlePrefix = titlePrefix, writerVariables = variables',
writerTabStop = tabStop, writerTabStop = tabStop,
writerTableOfContents = toc && writerTableOfContents = toc &&
writerName' /= "s5", writerName' /= "s5",
@ -647,8 +648,6 @@ main = do
writerIgnoreNotes = False, writerIgnoreNotes = False,
writerIncremental = incremental, writerIncremental = incremental,
writerNumberSections = numberSections, writerNumberSections = numberSections,
writerIncludeBefore = includeBefore,
writerIncludeAfter = includeAfter,
writerStrictMarkdown = strict, writerStrictMarkdown = strict,
writerReferenceLinks = referenceLinks, writerReferenceLinks = referenceLinks,
writerWrapText = wrap, writerWrapText = wrap,