diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 72 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 39 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 115 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 25 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 43 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/MediaWiki.hs | 29 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 45 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 41 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 23 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 90 | ||||
-rw-r--r-- | src/pandoc.hs | 41 |
13 files changed, 289 insertions, 288 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 6c131825a..868edc2c7 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -982,8 +982,6 @@ data WriterOptions = WriterOptions { writerStandalone :: Bool -- ^ Include header and footer , writerTemplate :: String -- ^ Template to use in standalone mode , 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 , writerTableOfContents :: Bool -- ^ Include table of contents , writerS5 :: Bool -- ^ We're writing S5 @@ -991,8 +989,6 @@ data WriterOptions = WriterOptions , writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc) , writerIncremental :: Bool -- ^ Incremental S5 lists , 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 , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , writerWrapText :: Bool -- ^ Wrap text to line length @@ -1007,8 +1003,6 @@ defaultWriterOptions = WriterOptions { writerStandalone = False , writerTemplate = "" , writerVariables = [] - , writerHeader = "" - , writerTitlePrefix = "" , writerTabStop = 4 , writerTableOfContents = False , writerS5 = False @@ -1016,8 +1010,6 @@ defaultWriterOptions = , writerIgnoreNotes = False , writerIncremental = False , writerNumberSections = False - , writerIncludeBefore = "" - , writerIncludeAfter = "" , writerStrictMarkdown = False , writerReferenceLinks = False , writerWrapText = True diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 142c862ef..0682de4bd 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -57,47 +57,49 @@ writeConTeXt options document = pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState Doc pandocToConTeXt options (Pandoc meta blocks) = do - 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 + 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 - 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" + 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" -- escape things as needed for ConTeXt diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index b46bb0eb4..8d1ea30e9 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -59,25 +59,26 @@ authorToDocbook name = inTagsIndented "author" $ -- | Convert Pandoc document to string in Docbook format. writeDocbook :: WriterOptions -> Pandoc -> String writeDocbook opts (Pandoc (Meta title authors date) blocks) = - let head' = if writerStandalone opts - then text (writerHeader opts) - else empty - meta = if writerStandalone opts - then inTagsIndented "articleinfo" $ - (inTagsSimple "title" (wrap opts title)) $$ - (vcat (map authorToDocbook authors)) $$ - (inTagsSimple "date" (text $ escapeStringForXML date)) - else empty - elements = hierarchicalize blocks - before = writerIncludeBefore opts - after = writerIncludeAfter opts - body = (if null before then empty else text before) $$ - vcat (map (elementToDocbook opts) elements) $$ - (if null after then empty else text after) - body' = if writerStandalone opts - then inTagsIndented "article" (meta $$ body) - else body - in render $ head' $$ body' $$ text "" + "" -- TODO +-- let head' = if writerStandalone opts +-- then text (writerHeader opts) +-- else empty +-- meta = if writerStandalone opts +-- then inTagsIndented "articleinfo" $ +-- (inTagsSimple "title" (wrap opts title)) $$ +-- (vcat (map authorToDocbook authors)) $$ +-- (inTagsSimple "date" (text $ escapeStringForXML date)) +-- else empty +-- elements = hierarchicalize blocks +-- before = writerIncludeBefore opts +-- after = writerIncludeAfter opts +-- body = (if null before then empty else text before) $$ +-- vcat (map (elementToDocbook opts) elements) $$ +-- (if null after then empty else text after) +-- body' = if writerStandalone opts +-- then inTagsIndented "article" (meta $$ body) +-- else body +-- in render $ head' $$ body' $$ text "" -- | Convert an Element to Docbook. elementToDocbook :: WriterOptions -> Element -> Doc diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 2d1a143ec..4e2eb4e26 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -88,63 +88,64 @@ writeHtmlString opts = -- | Convert Pandoc document to Html structure. writeHtml :: WriterOptions -> Pandoc -> Html -writeHtml opts (Pandoc (Meta tit authors date) blocks) = - let titlePrefix = writerTitlePrefix opts - (topTitle,st) = runState (inlineListToHtml opts tit) defaultWriterState - topTitle'' = stripTags $ showHtmlFragment topTitle - topTitle' = titlePrefix ++ - (if null topTitle'' || null titlePrefix - then "" - else " - ") ++ topTitle'' - metadata = thetitle << topTitle' +++ - meta ! [httpequiv "Content-Type", - content "text/html; charset=UTF-8"] +++ - meta ! [name "generator", content "pandoc"] +++ - (toHtmlFromList $ - map (\a -> meta ! [name "author", content a]) authors) +++ - (if null date - then noHtml - else meta ! [name "date", content date]) - titleHeader = if writerStandalone opts && not (null tit) && - not (writerS5 opts) - then h1 ! [theclass "title"] $ topTitle - else noHtml - sects = hierarchicalize blocks - toc = if writerTableOfContents opts - then evalState (tableOfContents opts sects) st - else noHtml - (blocks', st') = runState - (mapM (elementToHtml opts) sects >>= return . toHtmlFromList) - st - cssLines = stCSS st' - css = if S.null cssLines - then noHtml - else style ! [thetype "text/css"] $ primHtml $ - '\n':(unlines $ S.toList cssLines) - math = if stMath st' - then case writerHTMLMathMethod opts of - LaTeXMathML Nothing -> - primHtml latexMathMLScript - LaTeXMathML (Just url) -> - script ! - [src url, thetype "text/javascript"] $ - noHtml - JsMath (Just url) -> - script ! - [src url, thetype "text/javascript"] $ - noHtml - _ -> noHtml - else noHtml - head' = header $ metadata +++ math +++ css +++ - primHtml (renderTemplate [] $ writerHeader opts) - notes = reverse (stNotes st') - before = primHtml $ writerIncludeBefore opts - after = primHtml $ writerIncludeAfter opts - thebody = before +++ titleHeader +++ toc +++ blocks' +++ - footnoteSection notes +++ after - in if writerStandalone opts - then head' +++ body thebody - else thebody +writeHtml opts (Pandoc (Meta tit authors date) blocks) = + noHtml -- TODO +-- let titlePrefix = writerTitlePrefix opts +-- (topTitle,st) = runState (inlineListToHtml opts tit) defaultWriterState +-- topTitle'' = stripTags $ showHtmlFragment topTitle +-- topTitle' = titlePrefix ++ +-- (if null topTitle'' || null titlePrefix +-- then "" +-- else " - ") ++ topTitle'' +-- metadata = thetitle << topTitle' +++ +-- meta ! [httpequiv "Content-Type", +-- content "text/html; charset=UTF-8"] +++ +-- meta ! [name "generator", content "pandoc"] +++ +-- (toHtmlFromList $ +-- map (\a -> meta ! [name "author", content a]) authors) +++ +-- (if null date +-- then noHtml +-- else meta ! [name "date", content date]) +-- titleHeader = if writerStandalone opts && not (null tit) && +-- not (writerS5 opts) +-- then h1 ! [theclass "title"] $ topTitle +-- else noHtml +-- sects = hierarchicalize blocks +-- toc = if writerTableOfContents opts +-- then evalState (tableOfContents opts sects) st +-- else noHtml +-- (blocks', st') = runState +-- (mapM (elementToHtml opts) sects >>= return . toHtmlFromList) +-- st +-- cssLines = stCSS st' +-- css = if S.null cssLines +-- then noHtml +-- else style ! [thetype "text/css"] $ primHtml $ +-- '\n':(unlines $ S.toList cssLines) +-- math = if stMath st' +-- then case writerHTMLMathMethod opts of +-- LaTeXMathML Nothing -> +-- primHtml latexMathMLScript +-- LaTeXMathML (Just url) -> +-- script ! +-- [src url, thetype "text/javascript"] $ +-- noHtml +-- JsMath (Just url) -> +-- script ! +-- [src url, thetype "text/javascript"] $ +-- noHtml +-- _ -> noHtml +-- else noHtml +-- head' = header $ metadata +++ math +++ css +++ +-- primHtml (renderTemplate [] $ writerHeader opts) +-- notes = reverse (stNotes st') +-- before = primHtml $ writerIncludeBefore opts +-- after = primHtml $ writerIncludeAfter opts +-- thebody = before +++ titleHeader +++ toc +++ blocks' +++ +-- footnoteSection notes +++ after +-- in if writerStandalone opts +-- then head' +++ body thebody +-- else thebody -- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix prefixedId :: WriterOptions -> String -> HtmlAttr diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 78de1b17c..fadde0760 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -57,15 +57,13 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do then return "" else liftM render $ inlineListToLaTeX title let context = writerVariables options ++ - [ ("before", writerIncludeBefore options) - , ("after", writerIncludeAfter options) - , ("toc", if writerTableOfContents options then "yes" else "") + [ ("toc", if writerTableOfContents options then "yes" else "") , ("body", main) , ("title", titletext) , ("authors", intercalate "\\\\" $ map stringToLaTeX authors) , ("date", stringToLaTeX date) ] let templ = if writerStandalone options - then writerHeader options + then writerTemplate options else "$if(toc)$\\tableofcontents\n$endif$" ++ "$if(before)$$before$\n$endif$" ++ "$body$$if(after)$$after$\n$endif$" diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index f6f656c4e..7a04e38c4 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -48,18 +48,19 @@ writeMan opts document = render $ evalState (pandocToMan opts document) ([],[]) -- | Return groff man representation of document. pandocToMan :: WriterOptions -> Pandoc -> State WriterState Doc pandocToMan opts (Pandoc meta 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 - (head', foot) <- metaToMan opts meta - body <- blockListToMan opts blocks - (notes, preprocessors) <- get - let preamble = if null preprocessors || not (writerStandalone opts) - then empty - else text $ ".\\\" " ++ concat (nub preprocessors) - notes' <- notesToMan opts (reverse notes) - return $ preamble $$ head' $$ before' $$ body $$ notes' $$ foot $$ after' + return empty -- TODO +-- 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 +-- (head', foot) <- metaToMan opts meta +-- body <- blockListToMan opts blocks +-- (notes, preprocessors) <- get +-- let preamble = if null preprocessors || not (writerStandalone opts) +-- then empty +-- else text $ ".\\\" " ++ concat (nub preprocessors) +-- notes' <- notesToMan opts (reverse notes) +-- return $ preamble $$ head' $$ before' $$ body $$ notes' $$ foot $$ after' -- | Insert bibliographic information into Man header and footer. metaToMan :: WriterOptions -- ^ Options, including Man header diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 0e1231b62..e95b139a6 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -50,27 +50,28 @@ writeMarkdown opts document = -- | Return markdown representation of document. pandocToMarkdown :: WriterOptions -> Pandoc -> State WriterState Doc pandocToMarkdown opts (Pandoc meta blocks) = do - let before = writerIncludeBefore opts - let after = writerIncludeAfter opts - let header = writerHeader opts - let before' = if null before then empty else text before - let after' = if null after then empty else text after - let header' = if null header then empty else text header - metaBlock <- metaToMarkdown opts meta - let head' = if writerStandalone opts - then metaBlock $+$ header' - else empty - let headerBlocks = filter isHeaderBlock blocks - let toc = if writerTableOfContents opts - then tableOfContents opts headerBlocks - else empty - body <- blockListToMarkdown opts blocks - (notes, _) <- get - notes' <- notesToMarkdown opts (reverse notes) - (_, refs) <- get -- note that the notes may contain refs - refs' <- keyTableToMarkdown opts (reverse refs) - return $ head' $+$ before' $+$ toc $+$ body $+$ text "" $+$ - notes' $+$ text "" $+$ refs' $+$ after' + return empty -- TODO +-- let before = writerIncludeBefore opts +-- let after = writerIncludeAfter opts +-- let header = writerHeader opts +-- let before' = if null before then empty else text before +-- let after' = if null after then empty else text after +-- let header' = if null header then empty else text header +-- metaBlock <- metaToMarkdown opts meta +-- let head' = if writerStandalone opts +-- then metaBlock $+$ header' +-- else empty +-- let headerBlocks = filter isHeaderBlock blocks +-- let toc = if writerTableOfContents opts +-- then tableOfContents opts headerBlocks +-- else empty +-- body <- blockListToMarkdown opts blocks +-- (notes, _) <- get +-- notes' <- notesToMarkdown opts (reverse notes) +-- (_, refs) <- get -- note that the notes may contain refs +-- refs' <- keyTableToMarkdown opts (reverse refs) +-- return $ head' $+$ before' $+$ toc $+$ body $+$ text "" $+$ +-- notes' $+$ text "" $+$ refs' $+$ after' -- | Return markdown representation of reference key table. keyTableToMarkdown :: WriterOptions -> KeyTable -> State WriterState Doc diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 1e7194621..f3e0c58fa 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -52,20 +52,21 @@ 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 - let head' = if writerStandalone opts - then writerHeader opts - else "" - let toc = if writerTableOfContents opts - then "__TOC__\n" - else "" - body <- blockListToMediaWiki opts blocks - notesExist <- get >>= return . stNotes - let notes = if notesExist - then "\n== Notes ==\n<references />" - else "" - return $ head' ++ before ++ toc ++ body ++ after ++ notes + return "" -- TODO +-- let before = writerIncludeBefore opts +-- let after = writerIncludeAfter opts +-- let head' = if writerStandalone opts +-- then writerHeader opts +-- else "" +-- let toc = if writerTableOfContents opts +-- then "__TOC__\n" +-- else "" +-- body <- blockListToMediaWiki opts blocks +-- notesExist <- get >>= return . stNotes +-- let notes = if notesExist +-- then "\n== Notes ==\n<references />" +-- else "" +-- return $ head' ++ before ++ toc ++ body ++ after ++ notes -- | Escape special characters for MediaWiki. escapeString :: String -> String diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 15e7f30bd..df08146b3 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -180,28 +180,29 @@ authorToOpenDocument name = -- | Convert Pandoc document to string in OpenDocument format. writeOpenDocument :: WriterOptions -> Pandoc -> String writeOpenDocument opts (Pandoc (Meta title authors date) blocks) = - let root = inTags True "office:document-content" openDocumentNameSpaces - header = when (writerStandalone opts) $ text (writerHeader opts) - title' = case runState (wrap opts title) defaultWriterState of - (t,_) -> if isEmpty t then empty else inHeaderTags 1 t - authors' = when (authors /= []) $ vcat (map authorToOpenDocument authors) - date' = when (date /= []) $ - inParagraphTagsWithStyle "Date" (text $ escapeStringForXML date) - meta = when (writerStandalone opts) $ title' $$ authors' $$ date' - before = writerIncludeBefore opts - after = writerIncludeAfter opts - (doc, s) = runState (blocksToOpenDocument opts blocks) defaultWriterState - body = (if null before then empty else text before) $$ - doc $$ - (if null after then empty else text after) - body' = if writerStandalone opts - then inTagsIndented "office:body" $ - inTagsIndented "office:text" (meta $$ body) - else body - styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s - listStyle (n,l) = inTags True "text:list-style" [("style:name", "L" ++ show n)] (vcat l) - listStyles = map listStyle (stListStyles s) - in render $ header $$ root (generateStyles (styles ++ listStyles) $$ body' $$ text "") + "" -- TODO +-- let root = inTags True "office:document-content" openDocumentNameSpaces +-- header = when (writerStandalone opts) $ text (writerHeader opts) +-- title' = case runState (wrap opts title) defaultWriterState of +-- (t,_) -> if isEmpty t then empty else inHeaderTags 1 t +-- authors' = when (authors /= []) $ vcat (map authorToOpenDocument authors) +-- date' = when (date /= []) $ +-- inParagraphTagsWithStyle "Date" (text $ escapeStringForXML date) +-- meta = when (writerStandalone opts) $ title' $$ authors' $$ date' +-- before = writerIncludeBefore opts +-- after = writerIncludeAfter opts +-- (doc, s) = runState (blocksToOpenDocument opts blocks) defaultWriterState +-- body = (if null before then empty else text before) $$ +-- doc $$ +-- (if null after then empty else text after) +-- body' = if writerStandalone opts +-- then inTagsIndented "office:body" $ +-- inTagsIndented "office:text" (meta $$ body) +-- else body +-- styles = stTableStyles s ++ stParaStyles s ++ stTextStyles s +-- listStyle (n,l) = inTags True "text:list-style" [("style:name", "L" ++ show n)] (vcat l) +-- listStyles = map listStyle (stListStyles s) +-- in render $ header $$ root (generateStyles (styles ++ listStyles) $$ body' $$ text "") withParagraphStyle :: WriterOptions -> String -> [Block] -> State WriterState Doc withParagraphStyle o s (b:bs) diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 31c039bd7..a1c847385 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -57,26 +57,27 @@ writeRST opts document = -- | Return RST representation of document. pandocToRST :: Pandoc -> State WriterState Doc pandocToRST (Pandoc meta blocks) = do - opts <- get >>= (return . stOptions) - let before = writerIncludeBefore opts - after = writerIncludeAfter opts - header = writerHeader opts - before' = if null before then empty else text before - after' = if null after then empty else text after - header' = if null header then empty else text header - metaBlock <- metaToRST opts meta - let head' = if (writerStandalone opts) - then metaBlock $+$ header' - else empty - body <- blockListToRST blocks - includes <- get >>= (return . concat . stIncludes) - let includes' = if null includes then empty else text includes - notes <- get >>= (notesToRST . reverse . stNotes) - -- note that the notes may contain refs, so we do them first - refs <- get >>= (keyTableToRST . reverse . stLinks) - pics <- get >>= (pictTableToRST . reverse . stImages) - return $ head' $+$ before' $+$ includes' $+$ body $+$ notes $+$ text "" $+$ - refs $+$ pics $+$ after' + return empty -- TODO +-- opts <- get >>= (return . stOptions) +-- let before = writerIncludeBefore opts +-- after = writerIncludeAfter opts +-- header = writerHeader opts +-- before' = if null before then empty else text before +-- after' = if null after then empty else text after +-- header' = if null header then empty else text header +-- metaBlock <- metaToRST opts meta +-- let head' = if (writerStandalone opts) +-- then metaBlock $+$ header' +-- else empty +-- body <- blockListToRST blocks +-- includes <- get >>= (return . concat . stIncludes) +-- let includes' = if null includes then empty else text includes +-- notes <- get >>= (notesToRST . reverse . stNotes) +-- -- note that the notes may contain refs, so we do them first +-- refs <- get >>= (keyTableToRST . reverse . stLinks) +-- pics <- get >>= (pictTableToRST . reverse . stImages) +-- return $ head' $+$ before' $+$ includes' $+$ body $+$ notes $+$ text "" $+$ +-- refs $+$ pics $+$ after' -- | Return RST representation of reference key table. keyTableToRST :: KeyTable -> State WriterState Doc diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 15bac115d..a146d2133 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -37,17 +37,18 @@ import Data.Char ( ord, isDigit ) -- | Convert Pandoc to a string in rich text format. writeRTF :: WriterOptions -> Pandoc -> String writeRTF options (Pandoc meta blocks) = - let head' = if writerStandalone options - then rtfHeader (writerHeader options) meta - else "" - toc = if writerTableOfContents options - then tableOfContents $ filter isHeaderBlock blocks - else "" - foot = if writerStandalone options then "\n}\n" else "" - body = writerIncludeBefore options ++ - concatMap (blockToRTF 0 AlignDefault) blocks ++ - writerIncludeAfter options - in head' ++ toc ++ body ++ foot + "" -- TODO +-- let head' = if writerStandalone options +-- then rtfHeader (writerHeader options) meta +-- else "" +-- toc = if writerTableOfContents options +-- then tableOfContents $ filter isHeaderBlock blocks +-- else "" +-- foot = if writerStandalone options then "\n}\n" else "" +-- body = writerIncludeBefore options ++ +-- concatMap (blockToRTF 0 AlignDefault) blocks ++ +-- writerIncludeAfter options +-- in head' ++ toc ++ body ++ foot -- | Construct table of contents from list of header blocks. tableOfContents :: [Block] -> String diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 5b706d24b..1f126f34c 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -68,56 +68,58 @@ wrapTop (Pandoc (Meta title authors date) blocks) = pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState Doc pandocToTexinfo options (Pandoc meta blocks) = do - main <- blockListToTexinfo blocks - head' <- if writerStandalone options - then texinfoHeader options meta - else return empty - 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 - -- XXX toc untested - let toc = if writerTableOfContents options - then text "@contents" - else empty - let foot = if writerStandalone options - then text "@bye" - else empty - return $ head' $$ toc $$ body $$ foot + return empty -- TODO +-- main <- blockListToTexinfo blocks +-- head' <- if writerStandalone options +-- then texinfoHeader options meta +-- else return empty +-- 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 +-- -- XXX toc untested +-- let toc = if writerTableOfContents options +-- then text "@contents" +-- else empty +-- let foot = if writerStandalone options +-- then text "@bye" +-- else empty +-- return $ head' $$ toc $$ body $$ foot -- | Insert bibliographic information into Texinfo header. texinfoHeader :: WriterOptions -- ^ Options, including Texinfo header -> Meta -- ^ Meta with bibliographic information -> State WriterState Doc texinfoHeader options (Meta title authors date) = do - titletext <- if null title - then return empty - else do - t <- inlineListToTexinfo title - return $ text "@title " <> t - headerIncludes <- get >>= return . S.toList . stIncludes - let extras = text $ unlines headerIncludes - let authorstext = map makeAuthor authors - let datetext = if date == "" - then empty - else text $ stringToTexinfo date - - let baseHeader = case writerHeader options of - "" -> empty - x -> text x - let header = text "@documentencoding utf-8" $$ baseHeader $$ extras - return $ text "\\input texinfo" $$ - header $$ - text "@ifnottex" $$ - text "@paragraphindent 0" $$ - text "@end ifnottex" $$ - text "@titlepage" $$ - titletext $$ vcat authorstext $$ - datetext $$ - text "@end titlepage" + return empty -- TODO +-- titletext <- if null title +-- then return empty +-- else do +-- t <- inlineListToTexinfo title +-- return $ text "@title " <> t +-- headerIncludes <- get >>= return . S.toList . stIncludes +-- let extras = text $ unlines headerIncludes +-- let authorstext = map makeAuthor authors +-- let datetext = if date == "" +-- then empty +-- else text $ stringToTexinfo date +-- +-- let baseHeader = case writerHeader options of +-- "" -> empty +-- x -> text x +-- let header = text "@documentencoding utf-8" $$ baseHeader $$ extras +-- return $ text "\\input texinfo" $$ +-- header $$ +-- text "@ifnottex" $$ +-- text "@paragraphindent 0" $$ +-- text "@end ifnottex" $$ +-- text "@titlepage" $$ +-- titletext $$ vcat authorstext $$ +-- datetext $$ +-- text "@end titlepage" makeAuthor :: String -> Doc makeAuthor author = text $ "@author " ++ (stringToTexinfo author) diff --git a/src/pandoc.hs b/src/pandoc.hs index 71741dba3..b595f7e50 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -138,9 +138,6 @@ data Opt = Opt , optTemplate :: String -- ^ Custom template , optVariables :: [(String,String)] -- ^ Template variables to set , 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 , optNumberSections :: Bool -- ^ Number sections in LaTeX , optIncremental :: Bool -- ^ Use incremental lists in S5 @@ -177,9 +174,6 @@ defaultOpts = Opt , optTemplate = "" , optVariables = [] , optIncludeInHeader = "" - , optIncludeBeforeBody = "" - , optIncludeAfterBody = "" - , optTitlePrefix = "" , optOutputFile = "-" -- "-" means stdout , optNumberSections = False , optIncremental = False @@ -367,18 +361,28 @@ options = , Option "B" ["include-before-body"] (ReqArg (\arg opt -> do - let old = optIncludeBeforeBody opt 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") "" -- "File to include before document body" , Option "A" ["include-after-body"] (ReqArg (\arg opt -> do - let old = optIncludeAfterBody opt 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") "" -- "File to include after document body" @@ -397,8 +401,10 @@ options = , Option "T" ["title-prefix"] (ReqArg - (\arg opt -> return opt { optTitlePrefix = arg, - optStandalone = True }) + (\arg opt -> do + let newvars = ("title-prefix", arg) : optVariables opt + return opt { optVariables = newvars, + optStandalone = True }) "STRING") "" -- "String to prefix to HTML window title" @@ -549,9 +555,6 @@ main = do , optTableOfContents = toc , optTemplate = template , optIncludeInHeader = includeHeader - , optIncludeBeforeBody = includeBefore - , optIncludeAfterBody = includeAfter - , optTitlePrefix = titlePrefix , optOutputFile = outputFile , optNumberSections = numberSections , optIncremental = incremental @@ -633,12 +636,10 @@ main = do [("header-includes", includeHeader)] ++ variables let writerOptions = WriterOptions { writerStandalone = standalone', - writerTemplate = defaultTemplate, - writerVariables = variables', - writerHeader = if null template + writerTemplate = if null template then defaultTemplate else template, - writerTitlePrefix = titlePrefix, + writerVariables = variables', writerTabStop = tabStop, writerTableOfContents = toc && writerName' /= "s5", @@ -647,8 +648,6 @@ main = do writerIgnoreNotes = False, writerIncremental = incremental, writerNumberSections = numberSections, - writerIncludeBefore = includeBefore, - writerIncludeAfter = includeAfter, writerStrictMarkdown = strict, writerReferenceLinks = referenceLinks, writerWrapText = wrap, |