aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:12:44 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:12:44 +0000
commit3ec8772daff7d76097d7435c4e8da1df5ee4cc6a (patch)
tree9fc8b0101a1bd0016b619707f45bad9c6a2b9132 /src/Text/Pandoc/Writers
parent1a166987dfc049d03f034b920e4ae679402aa2f5 (diff)
downloadpandoc-3ec8772daff7d76097d7435c4e8da1df5ee4cc6a.tar.gz
Changed Meta author and date types to Inline lists instead of Strings.
Meta [Inline] [[Inline]] [Inline] rather than Meta [Inline] [String] String. This is a breaking change for libraries that use pandoc and manipulate the metadata. Changed .native files in test suite for new Meta format. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1699 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs10
-rw-r--r--src/Text/Pandoc/Writers/Man.hs10
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs21
-rw-r--r--src/Text/Pandoc/Writers/RST.hs11
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs6
-rw-r--r--src/Text/Pandoc/Writers/S5.hs8
6 files changed, 37 insertions, 29 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 92bf65b0a..f119598a6 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -53,15 +53,15 @@ writeLaTeX options document =
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
main <- liftM render $ blockListToLaTeX blocks
- titletext <- if null title
- then return ""
- else liftM render $ inlineListToLaTeX title
+ titletext <- liftM render $ inlineListToLaTeX title
+ authorsText <- mapM (liftM render . inlineListToLaTeX) authors
+ dateText <- liftM render $ inlineListToLaTeX date
let context = writerVariables options ++
[ ("toc", if writerTableOfContents options then "yes" else "")
, ("body", main)
, ("title", titletext)
- , ("authors", intercalate "\\\\" $ map stringToLaTeX authors)
- , ("date", stringToLaTeX date) ]
+ , ("authors", intercalate "\\\\" authorsText)
+ , ("date", dateText) ]
return $ renderTemplate context $ writerTemplate options
-- escape things as needed for LaTeX
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 7a04e38c4..64fd24ad0 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -68,6 +68,8 @@ metaToMan :: WriterOptions -- ^ Options, including Man header
-> State WriterState (Doc, Doc)
metaToMan options (Meta title authors date) = do
titleText <- inlineListToMan options title
+ authorsText <- mapM (inlineListToMan options) authors
+ dateText <- inlineListToMan options date
let (cmdName, rest) = break (== ' ') $ render titleText
let (title', section) = case reverse cmdName of
(')':d:'(':xs) | d `elem` ['0'..'9'] ->
@@ -76,11 +78,11 @@ metaToMan options (Meta title authors date) = do
let extras = map (doubleQuotes . text . removeLeadingTrailingSpace) $
splitBy '|' rest
let head' = (text ".TH") <+> title' <+> section <+>
- doubleQuotes (text date) <+> hsep extras
- let foot = case length authors of
+ doubleQuotes dateText <+> hsep extras
+ let foot = case length authorsText of
0 -> empty
- 1 -> text ".SH AUTHOR" $$ (text $ intercalate ", " authors)
- _ -> text ".SH AUTHORS" $$ (text $ intercalate ", " authors)
+ 1 -> text ".SH AUTHOR" $$ (hcat $ intersperse (text ", ") authorsText)
+ _ -> text ".SH AUTHORS" $$ (hcat $ intersperse (text ", ") authorsText)
return $ if writerStandalone options
then (head', foot)
else (empty, empty)
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index a72116376..266336968 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -109,8 +109,8 @@ metaToMarkdown :: WriterOptions -> Meta -> State WriterState Doc
metaToMarkdown _ (Meta [] [] []) = return empty
metaToMarkdown opts (Meta title authors date) = do
title' <- titleToMarkdown opts title
- authors' <- authorsToMarkdown authors
- date' <- dateToMarkdown date
+ authors' <- authorsToMarkdown opts authors
+ date' <- dateToMarkdown opts date
return $ title' $+$ authors' $+$ date' $+$ text ""
titleToMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc
@@ -119,14 +119,17 @@ titleToMarkdown opts lst = do
contents <- inlineListToMarkdown opts lst
return $ text "% " <> contents
-authorsToMarkdown :: [String] -> State WriterState Doc
-authorsToMarkdown [] = return empty
-authorsToMarkdown lst = return $
- text "% " <> text (intercalate ", " (map escapeString lst))
+authorsToMarkdown :: WriterOptions -> [[Inline]] -> State WriterState Doc
+authorsToMarkdown opts [] = return empty
+authorsToMarkdown opts lst = do
+ authors <- mapM (inlineListToMarkdown opts) lst
+ return $ text "% " <> (hcat $ intersperse (text ", ") authors)
-dateToMarkdown :: String -> State WriterState Doc
-dateToMarkdown [] = return empty
-dateToMarkdown str = return $ text "% " <> text (escapeString str)
+dateToMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc
+dateToMarkdown opts [] = return empty
+dateToMarkdown opts str = do
+ date <- inlineListToMarkdown opts str
+ return $ text "% " <> date
-- | Construct table of contents from list of header blocks.
tableOfContents :: WriterOptions -> [Block] -> Doc
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index a1c847385..2e01bb62e 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -150,15 +150,18 @@ titleToRST lst = do
let border = text (replicate titleLength '=')
return $ border $+$ contents $+$ border <> text "\n"
-authorsToRST :: [String] -> State WriterState Doc
+authorsToRST :: [[Inline]] -> State WriterState Doc
authorsToRST [] = return empty
authorsToRST (first:rest) = do
rest' <- authorsToRST rest
- return $ (text ":Author: " <> text first) $+$ rest'
+ first' <- inlineListToRST first
+ return $ (text ":Author: " <> first') $+$ rest'
-dateToRST :: String -> State WriterState Doc
+dateToRST :: [Inline] -> State WriterState Doc
dateToRST [] = return empty
-dateToRST str = return $ text ":Date: " <> text (escapeString str)
+dateToRST str = do
+ date <- inlineListToRST str
+ return $ text ":Date: " <> date
-- | Convert Pandoc block element to RST.
blockToRST :: Block -- ^ Block element
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index a146d2133..3830be705 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -152,10 +152,10 @@ rtfHeader headerText (Meta title authors date) =
authorstext = if null authors
then ""
else rtfPar 0 0 AlignCenter (" " ++ (intercalate "\\" $
- map stringToRTF authors))
- datetext = if date == ""
+ map inlineListToRTF authors))
+ datetext = if null date
then ""
- else rtfPar 0 0 AlignCenter (" " ++ stringToRTF date) in
+ else rtfPar 0 0 AlignCenter (" " ++ inlineListToRTF date) in
let spacer = if null (titletext ++ authorstext ++ datetext)
then ""
else rtfPar 0 0 AlignDefault "" in
diff --git a/src/Text/Pandoc/Writers/S5.hs b/src/Text/Pandoc/Writers/S5.hs
index 67ff673c2..c3acbfe71 100644
--- a/src/Text/Pandoc/Writers/S5.hs
+++ b/src/Text/Pandoc/Writers/S5.hs
@@ -85,9 +85,9 @@ writeS5String options = (writeHtmlString options) . insertS5Structure
-- | Inserts HTML needed for an S5 presentation (e.g. around slides).
layoutDiv :: [Inline] -- ^ Title of document (for header or footer)
- -> String -- ^ Date of document (for header or footer)
+ -> [Inline] -- ^ Date of document (for header or footer)
-> [Block] -- ^ List of block elements returned
-layoutDiv title' date = [(RawHtml "<div class=\"layout\">\n<div id=\"controls\"></div>\n<div id=\"currentSlide\"></div>\n<div id=\"header\"></div>\n<div id=\"footer\">\n"), (Header 1 [Str date]), (Header 2 title'), (RawHtml "</div>\n</div>\n")]
+layoutDiv title' date = [(RawHtml "<div class=\"layout\">\n<div id=\"controls\"></div>\n<div id=\"currentSlide\"></div>\n<div id=\"header\"></div>\n<div id=\"footer\">\n"), (Header 1 date), (Header 2 title'), (RawHtml "</div>\n</div>\n")]
presentationStart :: Block
presentationStart = RawHtml "<div class=\"presentation\">\n\n"
@@ -130,8 +130,8 @@ insertS5Structure (Pandoc (Meta title' authors date) blocks) =
let slides = insertSlides True blocks
firstSlide = if not (null title')
then [slideStart, (Header 1 title'),
- (Header 3 [Str (intercalate ", " authors)]),
- (Header 4 [Str date]), slideEnd]
+ (Header 3 (intercalate [Str ",", Space] authors)),
+ (Header 4 date), slideEnd]
else []
newBlocks = (layoutDiv title' date) ++ presentationStart:firstSlide ++
slides ++ [presentationEnd]