aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2006-10-17 14:22:29 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2006-10-17 14:22:29 +0000
commitdf7b68225101966051f8b592a27127bf789eb81e (patch)
treea063e97ed58d0bdb2cbb5a95c3e8c1bcce54aa00 /src/Text/Pandoc/Writers
parente7dbfef4d8aa528d9245424e9c372e900a774c90 (diff)
downloadpandoc-df7b68225101966051f8b592a27127bf789eb81e.tar.gz
initial import
git-svn-id: https://pandoc.googlecode.com/svn/trunk@2 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/DefaultHeaders.hs27
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs197
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs164
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs149
-rw-r--r--src/Text/Pandoc/Writers/RST.hs188
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs194
-rw-r--r--src/Text/Pandoc/Writers/S5.hs95
7 files changed, 1014 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Writers/DefaultHeaders.hs b/src/Text/Pandoc/Writers/DefaultHeaders.hs
new file mode 100644
index 000000000..87dd7d8ff
--- /dev/null
+++ b/src/Text/Pandoc/Writers/DefaultHeaders.hs
@@ -0,0 +1,27 @@
+----------------------------------------------------
+-- Do not edit this file by hand. Edit
+-- 'templates/DefaultHeaders.hs'
+-- and run ./fillTemplates.pl Text/Pandoc/Writers/DefaultHeaders.hs
+----------------------------------------------------
+
+-- | Default headers for Pandoc writers.
+module Text.Pandoc.Writers.DefaultHeaders (
+ defaultLaTeXHeader,
+ defaultHtmlHeader,
+ defaultS5Header,
+ defaultRTFHeader
+ ) where
+import Text.Pandoc.Writers.S5
+
+defaultLaTeXHeader :: String
+defaultLaTeXHeader = "\\documentclass{article}\n\\usepackage{hyperref}\n\\usepackage{ucs}\n\\usepackage[utf8x]{inputenc}\n\\usepackage{graphicx}\n\\setlength{\\parindent}{0pt}\n\\setlength{\\parskip}{6pt plus 2pt minus 1pt}\n% This is needed for code blocks in footnotes:\n\\usepackage{fancyvrb}\n\\VerbatimFootnotes\n"
+
+defaultHtmlHeader :: String
+defaultHtmlHeader = "<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 4.01 Transitional//EN\"\n \"http://www.w3.org/TR/html4/loose.dtd\">\n<html>\n<head>\n<meta http-equiv=\"Content-Type\" content=\"text/html; charset=UTF-8\" />\n<meta name=\"generator\" content=\"pandoc\" />\n<style type=\"text/css\">\ndiv.pandocNote { border-left: 1px solid grey; padding-left: 1em; }\nspan.pandocNoteRef { vertical-align: super; font-size: 80%; }\nspan.pandocNoteMarker { }\n</style>\n"
+
+defaultS5Header :: String
+defaultS5Header = "<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\" \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">\n<html xmlns=\"http://www.w3.org/1999/xhtml\">\n<head>\n<!-- configuration parameters -->\n<meta name=\"defaultView\" content=\"slideshow\" />\n<meta name=\"controlVis\" content=\"hidden\" />\n<meta http-equiv=\"Content-Type\" content=\"text/html; charset=UTF-8\" />\n<meta name=\"generator\" content=\"pandoc\" />\n" ++ s5CSS ++ s5Javascript
+
+defaultRTFHeader :: String
+defaultRTFHeader = "{\\rtf1\\ansi\\deff0{\\fonttbl{\\f0 Times New Roman;}{\\f1 Courier;}}\n{\\colortbl;\\red255\\green0\\blue0;\\red0\\green0\\blue255;}\n\\widowctrl\\hyphauto\n\n"
+
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
new file mode 100644
index 000000000..9eecf2761
--- /dev/null
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -0,0 +1,197 @@
+-- | Converts Pandoc to HTML.
+module Text.Pandoc.Writers.HTML (
+ writeHtml
+ ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared
+import Text.Html ( stringToHtmlString )
+import Text.Regex ( mkRegex )
+import Numeric ( showHex )
+import Char ( ord )
+import List ( isPrefixOf )
+
+-- | Convert Pandoc document to string in HTML format.
+writeHtml :: WriterOptions -> Pandoc -> String
+writeHtml options (Pandoc (Meta title authors date) blocks) =
+ let titlePrefix = writerTitlePrefix options in
+ let topTitle = if not (null titlePrefix) then
+ [Str titlePrefix] ++ (if not (null title) then [Str " - "] ++ title else [])
+ else
+ title in
+ let head = if (writerStandalone options) then
+ htmlHeader options (Meta topTitle authors date)
+ else
+ ""
+ titleBlocks = if (writerStandalone options) && (not (null title)) &&
+ (not (writerS5 options)) then
+ [RawHtml "<h1 class=\"title\">", Plain title, RawHtml "</h1>\n"]
+ else
+ []
+ foot = if (writerStandalone options) then "</body>\n</html>\n" else ""
+ body = (writerIncludeBefore options) ++
+ concatMap (blockToHtml options) (replaceReferenceLinks (titleBlocks ++ blocks)) ++
+ (writerIncludeAfter options) in
+ head ++ body ++ foot
+
+-- | Obfuscate a "mailto:" link using Javascript.
+obfuscateLink :: WriterOptions -> [Inline] -> String -> String
+obfuscateLink options text src =
+ let text' = inlineListToHtml options text in
+ let linkText = if src == ("mailto:" ++ text') then "e" else "'" ++ text' ++ "'"
+ altText = if src == ("mailto:" ++ text') then "\\1 [at] \\2" else text' ++ " (\\1 [at] \\2)" in
+ gsub "mailto:([^@]*)@(.*)" ("<script type=\"text/javascript\">h='\\2';n='\\1';e=n+'@'+h;document.write('<a href=\"mailto:'+e+'\">'+" ++ linkText ++ "+'<\\/a>');</script><noscript>" ++ altText ++ "</noscript>") src
+
+-- | Obfuscate character as entity.
+obfuscateChar :: Char -> String
+obfuscateChar char = let num = ord char in
+ let numstr = if even num then (show num) else ("x" ++ (showHex num "")) in
+ "&#" ++ numstr ++ ";"
+
+-- | Escape string, preserving character entities and quote.
+stringToHtml :: String -> String
+stringToHtml str = escapePreservingRegex stringToHtmlString (mkRegex "\"|(&[[:alnum:]]*;)") str
+
+-- | Escape string as in 'stringToHtml' but add smartypants filter.
+stringToSmartHtml :: String -> String
+stringToSmartHtml =
+ let escapeDoubleQuotes =
+ gsub "(\"|&quot;|'')" "&rdquo;" . -- rest are right quotes
+ gsub "([[:space:]])(\"|&quot;)" "\\1&ldquo;" . -- never right quo after space
+ gsub "(\"|&quot;|``)('|`|&lsquo;)([^[:punct:][:space:]])" "&ldquo;&lsquo;\\3" . -- "'word left
+ gsub "(\"|&quot;|``)([^[:punct:][:space:]])" "&ldquo;\\2" -- "word left
+ escapeSingleQuotes =
+ gsub "'" "&rsquo;" . -- otherwise right
+ gsub "([[:space:]])'" "\\1&lsquo;" . -- never right quo after space
+ gsub "`" "&lsquo;" . -- ` is left
+ gsub "([^[:punct:][:space:]])'" "\\1&rsquo;" . -- word' right
+ gsub "('|`)(\"|&quot;|&ldquo;|``)" "&lsquo;&ldquo;" . -- '"word left
+ gsub "^('|`)([^[:punct:][:space:]])" "&lsquo;\\2" . -- 'word left
+ gsub "([^[:punct:][:space:]])'(s|S)" "\\1&rsquo;\\2" . -- possessive
+ gsub "([[:space:]])'([^[:punct:][:space:]])" "\\1&lsquo;\\2" . -- 'word left
+ gsub "'([0-9][0-9](s|S))" "&rsquo;\\1" -- '80s - decade abbrevs.
+ escapeDashes = gsub " ?-- ?" "&mdash;" .
+ gsub " ?--- ?" "&mdash;" .
+ gsub "([0-9])--?([0-9])" "\\1&ndash;\\2"
+ escapeEllipses = gsub "\\.\\.\\.|\\. \\. \\." "&hellip;" in
+ escapeSingleQuotes . escapeDoubleQuotes . escapeDashes . escapeEllipses . stringToHtml
+
+-- | Escape code string as needed for HTML.
+codeStringToHtml :: String -> String
+codeStringToHtml [] = []
+codeStringToHtml (x:xs) = case x of
+ '&' -> "&amp;" ++ codeStringToHtml xs
+ '<' -> "&lt;" ++ codeStringToHtml xs
+ _ -> x:(codeStringToHtml xs)
+
+-- | Escape string to HTML appropriate for attributes
+attributeStringToHtml :: String -> String
+attributeStringToHtml = gsub "\"" "&quot;"
+
+-- | Returns an HTML header with appropriate bibliographic information.
+htmlHeader :: WriterOptions -> Meta -> String
+htmlHeader options (Meta title authors date) =
+ let titletext = if (null title) then
+ ""
+ else
+ "<title>" ++ (inlineListToHtml options title) ++ "</title>\n"
+ authortext = if (null authors) then
+ ""
+ else
+ "<meta name=\"author\" content=\"" ++
+ (joinWithSep ", " (map stringToHtml authors)) ++ "\" />\n"
+ datetext = if (date == "") then
+ ""
+ else
+ "<meta name=\"date\" content=\"" ++ (stringToHtml date) ++ "\" />\n" in
+ (writerHeader options) ++ authortext ++ datetext ++ titletext ++ "</head>\n<body>\n"
+
+-- | Convert Pandoc block element to HTML.
+blockToHtml :: WriterOptions -> Block -> String
+blockToHtml options Blank = "\n"
+blockToHtml options Null = ""
+blockToHtml options (Plain lst) = inlineListToHtml options lst
+blockToHtml options (Para lst) = "<p>" ++ (inlineListToHtml options lst) ++ "</p>\n"
+blockToHtml options (BlockQuote blocks) =
+ if (writerS5 options) then -- in S5, treat list in blockquote specially
+ -- if default is incremental, make it nonincremental; otherwise incremental
+ let inc = not (writerIncremental options) in
+ case blocks of
+ [BulletList lst] -> blockToHtml (options {writerIncremental = inc}) (BulletList lst)
+ [OrderedList lst] -> blockToHtml (options {writerIncremental = inc}) (OrderedList lst)
+ otherwise -> "<blockquote>\n" ++ (concatMap (blockToHtml options) blocks) ++
+ "</blockquote>\n"
+ else
+ "<blockquote>\n" ++ (concatMap (blockToHtml options) blocks) ++ "</blockquote>\n"
+blockToHtml options (Note ref lst) =
+ let marker = "<span class=\"pandocNoteMarker\"><a name=\"note_" ++ ref ++
+ "\" href=\"#ref_" ++ ref ++ "\">(" ++ ref ++ ")</a></span> " in
+ let contents = (concatMap (blockToHtml options) lst) in
+ let contents' = case contents of
+ ('<':'p':'>':rest) -> "<p class=\"first\">" ++ marker ++ rest ++ "\n"
+ otherwise -> marker ++ contents ++ "\n" in
+ "<div class=\"pandocNote\">\n" ++ contents' ++ "</div>\n"
+blockToHtml options (Key _ _) = ""
+blockToHtml options (CodeBlock str) = "<pre><code>" ++ (codeStringToHtml str) ++
+ "</code></pre>\n"
+blockToHtml options (RawHtml str) = str
+blockToHtml options (BulletList lst) =
+ let attribs = if (writerIncremental options) then " class=\"incremental\"" else "" in
+ "<ul" ++ attribs ++ ">\n" ++ (concatMap (listItemToHtml options) lst) ++ "</ul>\n"
+blockToHtml options (OrderedList lst) =
+ let attribs = if (writerIncremental options) then " class=\"incremental\"" else "" in
+ "<ol" ++ attribs ++ ">\n" ++ (concatMap (listItemToHtml options) lst) ++ "</ol>\n"
+blockToHtml options HorizontalRule = "<hr />\n"
+blockToHtml options (Header level lst) = if ((level > 0) && (level <= 6)) then
+ "<h" ++ (show level) ++ ">" ++
+ (inlineListToHtml options lst) ++
+ "</h" ++ (show level) ++ ">\n"
+ else
+ "<p>" ++ (inlineListToHtml options lst) ++ "</p>\n"
+listItemToHtml options list = "<li>" ++ (concatMap (blockToHtml options) list) ++ "</li>\n"
+
+-- | Convert list of Pandoc inline elements to HTML.
+inlineListToHtml :: WriterOptions -> [Inline] -> String
+inlineListToHtml options lst =
+ -- consolidate adjacent Str and Space elements for more intelligent
+ -- smartypants filtering
+ let lst' = consolidateList lst in
+ concatMap (inlineToHtml options) lst'
+
+-- | Convert Pandoc inline element to HTML.
+inlineToHtml :: WriterOptions -> Inline -> String
+inlineToHtml options (Emph lst) = "<em>" ++ (inlineListToHtml options lst) ++ "</em>"
+inlineToHtml options (Strong lst) = "<strong>" ++ (inlineListToHtml options lst) ++ "</strong>"
+inlineToHtml options (Code str) = "<code>" ++ (codeStringToHtml str) ++ "</code>"
+inlineToHtml options (Str str) = if (writerSmartypants options) then
+ stringToSmartHtml str
+ else
+ stringToHtml str
+inlineToHtml options (TeX str) = (codeStringToHtml str)
+inlineToHtml options (HtmlInline str) = str
+inlineToHtml options (LineBreak) = "<br />\n"
+inlineToHtml options Space = " "
+inlineToHtml options (Link text (Src src tit)) =
+ let title = attributeStringToHtml tit in
+ if (isPrefixOf "mailto:" src) then
+ obfuscateLink options text src
+ else
+ "<a href=\"" ++ (codeStringToHtml src) ++ "\"" ++
+ (if tit /= "" then " title=\"" ++ title ++ "\">" else ">") ++
+ (inlineListToHtml options text) ++ "</a>"
+inlineToHtml options (Link text (Ref [])) = "[" ++ (inlineListToHtml options text) ++ "]"
+inlineToHtml options (Link text (Ref ref)) = "[" ++ (inlineListToHtml options text) ++ "][" ++
+ (inlineListToHtml options ref) ++ "]" -- this is what markdown does, for better or worse
+inlineToHtml options (Image alt (Src source tit)) =
+ let title = attributeStringToHtml tit
+ alternate = inlineListToHtml options alt in
+ "<img src=\"" ++ source ++ "\"" ++
+ (if tit /= "" then " title=\"" ++ title ++ "\"" else "") ++
+ (if alternate /= "" then " alt=\"" ++ alternate ++ "\"" else "") ++ ">"
+inlineToHtml options (Image alternate (Ref [])) =
+ "![" ++ (inlineListToHtml options alternate) ++ "]"
+inlineToHtml options (Image alternate (Ref ref)) =
+ "![" ++ (inlineListToHtml options alternate) ++ "][" ++ (inlineListToHtml options ref) ++ "]"
+inlineToHtml options (NoteRef ref) =
+ "<span class=\"pandocNoteRef\"><a name=\"ref_" ++ ref ++ "\" href=\"#note_" ++ ref ++
+ "\">(" ++ ref ++ ")</a></span>"
+
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
new file mode 100644
index 000000000..b77789e90
--- /dev/null
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -0,0 +1,164 @@
+-- | Convert Pandoc to LaTeX.
+module Text.Pandoc.Writers.LaTeX (
+ writeLaTeX
+ ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared
+import List ( (\\) )
+
+-- | Convert Pandoc to LaTeX.
+writeLaTeX :: WriterOptions -> Pandoc -> String
+writeLaTeX options (Pandoc meta blocks) =
+ let notes = filter isNoteBlock blocks in -- assumes all notes are at outer level
+ let body = (writerIncludeBefore options) ++
+ (concatMap (blockToLaTeX notes) (replaceReferenceLinks blocks)) ++
+ (writerIncludeAfter options) in
+ let head = if writerStandalone options then
+ latexHeader notes options meta
+ else
+ "" in
+ let foot = if writerStandalone options then "\n\\end{document}\n" else "" in
+ head ++ body ++ foot
+
+-- | Insert bibliographic information into LaTeX header.
+latexHeader :: [Block] -- ^ List of note blocks to use in resolving note refs
+ -> WriterOptions -- ^ Options, including LaTeX header
+ -> Meta -- ^ Meta with bibliographic information
+ -> String
+latexHeader notes options (Meta title authors date) =
+ let titletext = if null title then
+ ""
+ else
+ "\\title{" ++ inlineListToLaTeX notes title ++ "}\n"
+ authorstext = if null authors then
+ ""
+ else
+ "\\author{" ++ (joinWithSep "\\\\" (map stringToLaTeX authors)) ++ "}\n"
+ datetext = if date == "" then
+ ""
+ else
+ "\\date{" ++ stringToLaTeX date ++ "}\n"
+ maketitle = if null title then
+ ""
+ else
+ "\\maketitle\n"
+ secnumline = if (writerNumberSections options) then
+ ""
+ else
+ "\\setcounter{secnumdepth}{0}\n"
+ header = writerHeader options in
+ header ++ secnumline ++ titletext ++ authorstext ++ datetext ++ "\\begin{document}\n" ++ maketitle
+
+
+-- escape things as needed for LaTeX (also ldots, dashes, quotes, etc.)
+
+escapeBrackets = backslashEscape "{}"
+escapeSpecial = backslashEscape "$%&~_#"
+
+escapeBackslash = gsub "\\\\" "\\\\textbackslash{}"
+fixBackslash = gsub "\\\\textbackslash\\\\\\{\\\\\\}" "\\\\textbackslash{}"
+escapeHat = gsub "\\^" "\\\\^{}"
+escapeBar = gsub "\\|" "\\\\textbar{}"
+escapeLt = gsub "<" "\\\\textless{}"
+escapeGt = gsub ">" "\\\\textgreater{}"
+
+escapeDoubleQuotes =
+ gsub "\"" "''" . -- rest are right quotes
+ gsub "([[:space:]])\"" "\\1``" . -- never right quote after space
+ gsub "\"('|`)([^[:punct:][:space:]])" "``{}`\\2" . -- "'word left
+ gsub "\"([^[:punct:][:space:]])" "``\\1" -- "word left
+
+escapeSingleQuotes =
+ gsub "('|`)(\"|``)" "`{}``" . -- '"word left
+ gsub "([^[:punct:][:space:]])`(s|S)" "\\1'\\2" . -- catch possessives
+ gsub "^'([^[:punct:][:space:]])" "`\\1" . -- 'word left
+ gsub "([[:space:]])'" "\\1`" . -- never right quote after space
+ gsub "([[:space:]])'([^[:punct:][:space:]])" "\\1`\\2" -- 'word left (leave possessives)
+
+escapeEllipses = gsub "\\.\\.\\.|\\. \\. \\." "\\ldots{}"
+
+escapeDashes = gsub "([0-9])-([0-9])" "\\1--\\2" .
+ gsub " -- " "---" .
+ gsub "([^[:punct:][:space:]])--([^[:punct:][:space:]])" "\\1---\\2"
+
+escapeSmart = escapeSingleQuotes . escapeDoubleQuotes . escapeDashes . escapeEllipses
+
+-- | Escape string for LaTeX (including smart quotes, dashes, ellipses)
+stringToLaTeX :: String -> String
+stringToLaTeX = escapeSmart . escapeGt . escapeLt . escapeBar . escapeHat .
+ escapeSpecial . fixBackslash . escapeBrackets . escapeBackslash
+
+-- | Remove all code elements from list of inline elements
+-- (because it's illegal to have a \\verb inside a command argument)
+deVerb :: [Inline] -> [Inline]
+deVerb [] = []
+deVerb ((Code str):rest) = (Str str):(deVerb rest)
+deVerb (other:rest) = other:(deVerb rest)
+
+-- | Convert Pandoc block element to LaTeX.
+blockToLaTeX :: [Block] -- ^ List of note blocks to use in resolving note refs
+ -> Block -- ^ Block to convert
+ -> String
+blockToLaTeX notes Blank = "\n"
+blockToLaTeX notes Null = ""
+blockToLaTeX notes (Plain lst) = inlineListToLaTeX notes lst ++ "\n"
+blockToLaTeX notes (Para lst) = (inlineListToLaTeX notes lst) ++ "\n\n"
+blockToLaTeX notes (BlockQuote lst) =
+ "\\begin{quote}\n" ++ (concatMap (blockToLaTeX notes) lst) ++ "\\end{quote}\n"
+blockToLaTeX notes (Note ref lst) = ""
+blockToLaTeX notes (Key _ _) = ""
+blockToLaTeX notes (CodeBlock str) = "\\begin{verbatim}\n" ++ str ++ "\\end{verbatim}\n"
+blockToLaTeX notes (RawHtml str) = ""
+blockToLaTeX notes (BulletList lst) =
+ "\\begin{itemize}\n" ++ (concatMap (listItemToLaTeX notes) lst) ++ "\\end{itemize}\n"
+blockToLaTeX notes (OrderedList lst) =
+ "\\begin{enumerate}\n" ++ (concatMap (listItemToLaTeX notes) lst) ++ "\\end{enumerate}\n"
+blockToLaTeX notes HorizontalRule = "\\begin{center}\\rule{3in}{0.4pt}\\end{center}\n\n"
+blockToLaTeX notes (Header level lst) =
+ if (level > 0) && (level <= 3) then
+ "\\" ++ (concat (replicate (level - 1) "sub")) ++ "section{" ++
+ (inlineListToLaTeX notes (deVerb lst)) ++ "}\n\n"
+ else
+ (inlineListToLaTeX notes lst) ++ "\n\n"
+listItemToLaTeX notes list = "\\item " ++ (concatMap (blockToLaTeX notes) list)
+
+-- | Convert list of inline elements to LaTeX.
+inlineListToLaTeX :: [Block] -- ^ List of note blocks to use in resolving note refs
+ -> [Inline] -- ^ Inlines to convert
+ -> String
+inlineListToLaTeX notes lst =
+ -- first, consolidate Str and Space for more effective smartquotes:
+ let lst' = consolidateList lst in
+ concatMap (inlineToLaTeX notes) lst'
+
+-- | Convert inline element to LaTeX
+inlineToLaTeX :: [Block] -- ^ List of note blocks to use in resolving note refs
+ -> Inline -- ^ Inline to convert
+ -> String
+inlineToLaTeX notes (Emph lst) = "\\emph{" ++ (inlineListToLaTeX notes (deVerb lst)) ++ "}"
+inlineToLaTeX notes (Strong lst) = "\\textbf{" ++ (inlineListToLaTeX notes (deVerb lst)) ++ "}"
+inlineToLaTeX notes (Code str) = "\\verb" ++ [chr] ++ stuffing ++ [chr]
+ where stuffing = str
+ chr = ((enumFromTo '!' '~') \\ stuffing) !! 0
+inlineToLaTeX notes (Str str) = stringToLaTeX str
+inlineToLaTeX notes (TeX str) = str
+inlineToLaTeX notes (HtmlInline str) = ""
+inlineToLaTeX notes (LineBreak) = "\\\\\n"
+inlineToLaTeX notes Space = " "
+inlineToLaTeX notes (Link text (Src src tit)) =
+ "\\href{" ++ src ++ "}{" ++ (inlineListToLaTeX notes (deVerb text)) ++ "}"
+inlineToLaTeX notes (Link text (Ref [])) = "[" ++ (inlineListToLaTeX notes text) ++ "]"
+inlineToLaTeX notes (Link text (Ref ref)) = "[" ++ (inlineListToLaTeX notes text) ++ "][" ++
+ (inlineListToLaTeX notes ref) ++ "]" -- this is what markdown does, for better or worse
+inlineToLaTeX notes (Image alternate (Src source tit)) = "\\includegraphics{" ++ source ++ "}"
+inlineToLaTeX notes (Image alternate (Ref [])) =
+ "![" ++ (inlineListToLaTeX notes alternate) ++ "]"
+inlineToLaTeX notes (Image alternate (Ref ref)) =
+ "![" ++ (inlineListToLaTeX notes alternate) ++ "][" ++ (inlineListToLaTeX notes ref) ++ "]"
+inlineToLaTeX [] (NoteRef ref) = ""
+inlineToLaTeX ((Note firstref firstblocks):rest) (NoteRef ref) =
+ if (firstref == ref) then
+ "\\footnote{" ++ (stripTrailingNewlines (concatMap (blockToLaTeX rest) firstblocks)) ++ "}"
+ else
+ inlineToLaTeX rest (NoteRef ref)
+
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
new file mode 100644
index 000000000..b73090f62
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -0,0 +1,149 @@
+-- | Converts Pandoc to Markdown.
+module Text.Pandoc.Writers.Markdown (
+ writeMarkdown
+ ) where
+import Text.Regex ( matchRegex, mkRegex )
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared
+import Text.PrettyPrint.HughesPJ hiding ( Str )
+
+-- | Convert Pandoc to Markdown.
+writeMarkdown :: WriterOptions -> Pandoc -> String
+writeMarkdown options (Pandoc meta blocks) =
+ let body = text (writerIncludeBefore options) <>
+ vcat (map (blockToMarkdown (writerTabStop options)) (formatKeys blocks)) $$
+ text (writerIncludeAfter options) in
+ let head = if (writerStandalone options) then
+ ((metaToMarkdown meta) $$ text (writerHeader options))
+ else
+ empty in
+ render $ head <> body
+
+-- | Escape special characters for Markdown.
+escapeString :: String -> String
+escapeString = backslashEscape "`<\\*_^"
+
+-- | Escape embedded \" in link title.
+escapeLinkTitle :: String -> String
+escapeLinkTitle = gsub "\"" "\\\\\""
+
+-- | Take list of inline elements and return wrapped doc.
+wrappedMarkdown :: [Inline] -> Doc
+wrappedMarkdown lst = fsep $ map (fcat . (map inlineToMarkdown)) (splitBySpace lst)
+
+-- | Insert Blank block between key and non-key
+formatKeys :: [Block] -> [Block]
+formatKeys [] = []
+formatKeys [x] = [x]
+formatKeys ((Key x1 y1):(Key x2 y2):rest) = (Key x1 y1):(formatKeys ((Key x2 y2):rest))
+formatKeys ((Key x1 y1):rest) = (Key x1 y1):Blank:(formatKeys rest)
+formatKeys (x:(Key x1 y1):rest) = x:Blank:(formatKeys ((Key x1 y1):rest))
+formatKeys (x:rest) = x:(formatKeys rest)
+
+-- | Convert bibliographic information into Markdown header.
+metaToMarkdown :: Meta -> Doc
+metaToMarkdown (Meta [] [] "") = empty
+metaToMarkdown (Meta title [] "") = (titleToMarkdown title) <> (text "\n")
+metaToMarkdown (Meta title authors "") =
+ (titleToMarkdown title) <> (text "\n") <> (authorsToMarkdown authors) <> (text "\n")
+metaToMarkdown (Meta title authors date) =
+ (titleToMarkdown title) <> (text "\n") <> (authorsToMarkdown authors) <>
+ (text "\n") <> (dateToMarkdown date) <> (text "\n")
+
+titleToMarkdown :: [Inline] -> Doc
+titleToMarkdown lst = text "% " <> (inlineListToMarkdown lst)
+
+authorsToMarkdown :: [String] -> Doc
+authorsToMarkdown lst = text "% " <> text (joinWithSep ", " (map escapeString lst))
+
+dateToMarkdown :: String -> Doc
+dateToMarkdown str = text "% " <> text (escapeString str)
+
+-- | Convert Pandoc block element to markdown.
+blockToMarkdown :: Int -- ^ Tab stop
+ -> Block -- ^ Block element
+ -> Doc
+blockToMarkdown tabStop Blank = text ""
+blockToMarkdown tabStop Null = empty
+blockToMarkdown tabStop (Plain lst) = wrappedMarkdown lst
+blockToMarkdown tabStop (Para lst) = (wrappedMarkdown lst) <> (text "\n")
+blockToMarkdown tabStop (BlockQuote lst) =
+ (vcat $ map (\line -> (text "> ") <> (text line)) $ lines $ render $ vcat $
+ map (blockToMarkdown tabStop) lst) <> (text "\n")
+blockToMarkdown tabStop (Note ref lst) =
+ let lns = lines $ render $ vcat $ map (blockToMarkdown tabStop) lst in
+ if null lns then
+ empty
+ else
+ let first = head lns
+ rest = tail lns in
+ text ("^(" ++ (escapeString ref) ++ ") ") <> (text first) $$ (vcat $
+ map (\line -> (text "^ ") <> (text line)) rest) <> (text "\n")
+blockToMarkdown tabStop (Key txt (Src src tit)) =
+ text " " <> char '[' <> inlineListToMarkdown txt <> char ']' <> text ": " <> text src <>
+ (if tit /= "" then (text (" \"" ++ (escapeLinkTitle tit) ++ "\"")) else empty)
+blockToMarkdown tabStop (CodeBlock str) = (nest tabStop $ vcat $ map text (lines str)) <>
+ (if (endsWith '\n' str) then empty else text "\n") <> text "\n"
+blockToMarkdown tabStop (RawHtml str) = text str
+blockToMarkdown tabStop (BulletList lst) =
+ vcat (map (bulletListItemToMarkdown tabStop) lst) <> text "\n"
+blockToMarkdown tabStop (OrderedList lst) =
+ vcat (zipWith (orderedListItemToMarkdown tabStop) (enumFromTo 1 (length lst)) lst) <>
+ text "\n"
+blockToMarkdown tabStop HorizontalRule = text "\n* * * * *\n"
+blockToMarkdown tabStop (Header level lst) =
+ text ((replicate level '#') ++ " ") <> (inlineListToMarkdown lst) <> (text "\n")
+bulletListItemToMarkdown tabStop list =
+ hang (text "- ") tabStop (vcat (map (blockToMarkdown tabStop) list))
+
+-- | Convert ordered list item (a list of blocks) to markdown.
+orderedListItemToMarkdown :: Int -- ^ tab stop
+ -> Int -- ^ ordinal number of list item
+ -> [Block] -- ^ list item (list of blocks)
+ -> Doc
+orderedListItemToMarkdown tabStop num list =
+ hang (text ((show num) ++ "." ++ spacer)) tabStop (vcat (map (blockToMarkdown tabStop) list))
+ where spacer = if (num < 10) then " " else ""
+
+-- | Convert list of Pandoc inline elements to markdown.
+inlineListToMarkdown :: [Inline] -> Doc
+inlineListToMarkdown lst = hcat $ map inlineToMarkdown lst
+
+-- | Convert Pandoc inline element to markdown.
+inlineToMarkdown :: Inline -> Doc
+inlineToMarkdown (Emph lst) = text "*" <> (inlineListToMarkdown lst) <> text "*"
+inlineToMarkdown (Strong lst) = text "**" <> (inlineListToMarkdown lst) <> text "**"
+inlineToMarkdown (Code str) =
+ case (matchRegex (mkRegex "``") str) of
+ Just match -> text ("` " ++ str ++ " `")
+ Nothing -> case (matchRegex (mkRegex "`") str) of
+ Just match -> text ("`` " ++ str ++ " ``")
+ Nothing -> text ("`" ++ str ++ "`")
+inlineToMarkdown (Str str) = text $ escapeString str
+inlineToMarkdown (TeX str) = text str
+inlineToMarkdown (HtmlInline str) = text str
+inlineToMarkdown (LineBreak) = text " \n"
+inlineToMarkdown Space = char ' '
+inlineToMarkdown (Link txt (Src src tit)) =
+ let linktext = if (null txt) || (txt == [Str ""]) then
+ text "link"
+ else
+ inlineListToMarkdown txt in
+ char '[' <> linktext <> char ']' <> char '(' <> text src <>
+ (if tit /= "" then (text (" \"" ++ (escapeLinkTitle tit) ++ "\"")) else empty) <> char ')'
+inlineToMarkdown (Link txt (Ref [])) = char '[' <> inlineListToMarkdown txt <> text "][]"
+inlineToMarkdown (Link txt (Ref ref)) = char '[' <> inlineListToMarkdown txt <> char ']' <>
+ char '[' <> inlineListToMarkdown ref <> char ']'
+inlineToMarkdown (Image alternate (Src source tit)) =
+ let alt = if (null alternate) || (alternate == [Str ""]) then
+ text "image"
+ else
+ inlineListToMarkdown alternate in
+ char '!' <> char '[' <> alt <> char ']' <> char '(' <> text source <>
+ (if tit /= "" then (text (" \"" ++ (escapeLinkTitle tit) ++ "\"")) else empty) <> char ')'
+inlineToMarkdown (Image alternate (Ref [])) =
+ char '!' <> char '[' <> inlineListToMarkdown alternate <> char ']'
+inlineToMarkdown (Image alternate (Ref ref)) =
+ char '!' <> char '[' <> inlineListToMarkdown alternate <> char ']' <>
+ char '[' <> inlineListToMarkdown ref <> char ']'
+inlineToMarkdown (NoteRef ref) = char '^' <> char '(' <> text (escapeString ref) <> char ')'
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
new file mode 100644
index 000000000..37d895336
--- /dev/null
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -0,0 +1,188 @@
+-- | Converts Pandoc to reStructuredText.
+module Text.Pandoc.Writers.RST (
+ writeRST
+ ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared
+import List ( nubBy )
+import Text.PrettyPrint.HughesPJ hiding ( Str )
+
+-- | Convert Pandoc to reStructuredText.
+writeRST :: WriterOptions -> Pandoc -> String
+writeRST options (Pandoc meta blocks) =
+ let (main, refs) = unzip $ map (blockToRST (writerTabStop options))
+ (reformatBlocks $ replaceReferenceLinks blocks)
+ top = if (writerStandalone options) then
+ (metaToRST meta) $$ text (writerHeader options)
+ else
+ empty in
+ let refs' = nubBy (\x y -> (render x) == (render y)) refs in -- remove duplicate keys
+ let body = text (writerIncludeBefore options) <>
+ vcat main $$ text (writerIncludeAfter options) in
+ render $ top <> body $$ vcat refs'
+
+-- | Escape special RST characters.
+escapeString :: String -> String
+escapeString = backslashEscape "`\\|*_"
+
+-- | Convert list of inline elements into one 'Doc' of wrapped text and another
+-- containing references.
+wrappedRST :: [Inline] -> (Doc, Doc)
+wrappedRST lst =
+ let words = splitBySpace lst in
+ (fsep $ map (fcat . (map (fst . inlineToRST))) words, vcat (map (snd . inlineToRST) lst))
+
+-- | Remove reference keys, and make sure there are blanks before each list.
+reformatBlocks :: [Block] -> [Block]
+reformatBlocks [] = []
+reformatBlocks ((Plain x):(OrderedList y):rest) =
+ (Para x):(reformatBlocks ((OrderedList y):rest))
+reformatBlocks ((Plain x):(BulletList y):rest) = (Para x):(reformatBlocks ((BulletList y):rest))
+reformatBlocks ((OrderedList x):rest) =
+ (OrderedList (map reformatBlocks x)):(reformatBlocks rest)
+reformatBlocks ((BulletList x):rest) = (BulletList (map reformatBlocks x)):(reformatBlocks rest)
+reformatBlocks ((BlockQuote x):rest) = (BlockQuote (reformatBlocks x)):(reformatBlocks rest)
+reformatBlocks ((Note ref x):rest) = (Note ref (reformatBlocks x)):(reformatBlocks rest)
+reformatBlocks ((Key x1 y1):rest) = reformatBlocks rest
+reformatBlocks (x:rest) = x:(reformatBlocks rest)
+
+-- | Convert bibliographic information to 'Doc'.
+metaToRST :: Meta -> Doc
+metaToRST (Meta title authors date) =
+ (titleToRST title) <> (authorsToRST authors) <> (dateToRST date)
+
+-- | Convert title to 'Doc'.
+titleToRST :: [Inline] -> Doc
+titleToRST [] = empty
+titleToRST lst =
+ let title = fst $ inlineListToRST lst in
+ let titleLength = length $ render title in
+ let border = text (replicate titleLength '=') in
+ border <> char '\n' <> title <> char '\n' <> border <> text "\n\n"
+
+-- | Convert author list to 'Doc'.
+authorsToRST :: [String] -> Doc
+authorsToRST [] = empty
+authorsToRST (first:rest) = text ":Author: " <> text first <> char '\n' <> (authorsToRST rest)
+
+-- | Convert date to 'Doc'.
+dateToRST :: String -> Doc
+dateToRST [] = empty
+dateToRST str = text ":Date: " <> text (escapeString str) <> char '\n'
+
+-- | Convert Pandoc block element to a 'Doc' containing the main text and
+-- another one containing any references.
+blockToRST :: Int -- ^ tab stop
+ -> Block -- ^ block element to convert
+ -> (Doc, Doc) -- ^ first element is text, second is references for end of file
+blockToRST tabStop Blank = (text "\n", empty)
+blockToRST tabStop Null = (empty, empty)
+blockToRST tabStop (Plain lst) = wrappedRST lst
+blockToRST tabStop (Para [TeX str]) = -- raw latex block
+ let str' = if (endsWith '\n' str) then (str ++ "\n") else (str ++ "\n\n") in
+ (hang (text "\n.. raw:: latex\n") 3 (vcat $ map text (lines str')), empty)
+blockToRST tabStop (Para lst) = ((fst $ wrappedRST lst) <> (text "\n"), snd $ wrappedRST lst)
+blockToRST tabStop (BlockQuote lst) =
+ let (main, refs) = unzip $ map (blockToRST tabStop) lst in
+ ((nest tabStop $ vcat $ main) <> text "\n", vcat refs)
+blockToRST tabStop (Note ref blocks) =
+ let (main, refs) = unzip $ map (blockToRST tabStop) blocks in
+ ((hang (text ".. [" <> text (escapeString ref) <> text "] ") 3 (vcat main)), vcat refs)
+blockToRST tabStop (Key txt (Src src tit)) =
+ (text "ERROR - KEY FOUND", empty) -- shouldn't have a key here
+blockToRST tabStop (CodeBlock str) =
+ (hang (text "::\n") tabStop (vcat $ map text (lines ('\n':(str ++ "\n")))), empty)
+blockToRST tabStop (RawHtml str) =
+ let str' = if (endsWith '\n' str) then (str ++ "\n") else (str ++ "\n\n") in
+ (hang (text "\n.. raw:: html\n") 3 (vcat $ map text (lines str')), empty)
+blockToRST tabStop (BulletList lst) =
+ let (main, refs) = unzip $ map (bulletListItemToRST tabStop) lst in
+ (vcat main <> text "\n", vcat refs)
+blockToRST tabStop (OrderedList lst) =
+ let (main, refs) =
+ unzip $ zipWith (orderedListItemToRST tabStop) (enumFromTo 1 (length lst)) lst in
+ (vcat main <> text "\n", vcat refs)
+blockToRST tabStop HorizontalRule = (text "--------------\n", empty)
+blockToRST tabStop (Header level lst) =
+ let (headerText, refs) = inlineListToRST lst in
+ let headerLength = length $ render headerText in
+ let headerChar = if (level > 5) then ' ' else "=-~^'" !! (level - 1) in
+ let border = text $ replicate headerLength headerChar in
+ (headerText <> char '\n' <> border <> char '\n', refs)
+
+-- | Convert bullet list item (list of blocks) to reStructuredText.
+-- Returns a pair of 'Doc', the first the main text, the second references
+bulletListItemToRST :: Int -- ^ tab stop
+ -> [Block] -- ^ list item (list of blocks)
+ -> (Doc, Doc)
+bulletListItemToRST tabStop list =
+ let (main, refs) = unzip $ map (blockToRST tabStop) list in
+ (hang (text "- ") tabStop (vcat main), (vcat refs))
+
+-- | Convert an ordered list item (list of blocks) to reStructuredText.
+-- Returns a pair of 'Doc', the first the main text, the second references
+orderedListItemToRST :: Int -- ^ tab stop
+ -> Int -- ^ ordinal number of list item
+ -> [Block] -- ^ list item (list of blocks)
+ -> (Doc, Doc)
+orderedListItemToRST tabStop num list =
+ let (main, refs) = unzip $ map (blockToRST tabStop) list
+ spacer = if (length (show num) < 2) then " " else "" in
+ (hang (text ((show num) ++ "." ++ spacer)) tabStop (vcat main), (vcat refs))
+
+-- | Convert a list of inline elements to reStructuredText.
+-- Returns a pair of 'Doc', the first the main text, the second references.
+inlineListToRST :: [Inline] -> (Doc, Doc)
+inlineListToRST lst = let (main, refs) = unzip $ map inlineToRST lst in
+ (hcat main, hcat refs)
+
+-- | Convert an inline element to reStructuredText.
+-- Returns a pair of 'Doc', the first the main text, the second references.
+inlineToRST :: Inline -> (Doc, Doc) -- second Doc is list of refs for end of file
+inlineToRST (Emph lst) = let (main, refs) = inlineListToRST lst in
+ (text "*" <> main <> text "*", refs)
+inlineToRST (Strong lst) = let (main, refs) = inlineListToRST lst in
+ (text "**" <> main <> text "**", refs)
+inlineToRST (Code str) = (text $ "``" ++ str ++ "``", empty)
+inlineToRST (Str str) = (text $ escapeString str, empty)
+inlineToRST (TeX str) = (text str, empty)
+inlineToRST (HtmlInline str) = (empty, empty)
+inlineToRST (LineBreak) = inlineToRST Space -- RST doesn't have line breaks
+inlineToRST Space = (char ' ', empty)
+--
+-- Note: can assume reference links have been replaced where possible with explicit links.
+--
+inlineToRST (Link txt (Src src tit)) =
+ let (linktext, ref') = if (null txt) || (txt == [Str ""]) then
+ (text "link", empty)
+ else
+ inlineListToRST $ normalizeSpaces txt in
+ let link = char '`' <> linktext <> text "`_"
+ linktext' = render linktext in
+ let linktext'' = if (':' `elem` linktext') then "`" ++ linktext' ++ "`" else linktext' in
+ let ref = text ".. _" <> text linktext'' <> text ": " <> text src in
+ (link, ref' $$ ref)
+inlineToRST (Link txt (Ref [])) =
+ let (linktext, refs) = inlineListToRST txt in
+ (char '[' <> linktext <> char ']', refs)
+inlineToRST (Link txt (Ref ref)) =
+ let (linktext, refs1) = inlineListToRST txt
+ (reftext, refs2) = inlineListToRST ref in
+ (char '[' <> linktext <> text "][" <> reftext <> char ']', refs1 $$ refs2)
+inlineToRST (Image alternate (Src source tit)) =
+ let (alt, ref') = if (null alternate) || (alternate == [Str ""]) then
+ (text "image", empty)
+ else
+ inlineListToRST $ normalizeSpaces alternate in
+ let link = char '|' <> alt <> char '|' in
+ let ref = text ".. " <> link <> text " image:: " <> text source in
+ (link, ref' $$ ref)
+inlineToRST (Image alternate (Ref [])) =
+ let (alttext, refs) = inlineListToRST alternate in
+ (char '|' <> alttext <> char '|', refs)
+-- The following case won't normally occur...
+inlineToRST (Image alternate (Ref ref)) =
+ let (alttext, refs1) = inlineListToRST alternate
+ (reftext, refs2) = inlineListToRST ref in
+ (char '|' <> alttext <> char '|', refs1 $$ refs2)
+inlineToRST (NoteRef ref) = (text " [" <> text (escapeString ref) <> char ']' <> char '_', empty)
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
new file mode 100644
index 000000000..64f17cc74
--- /dev/null
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -0,0 +1,194 @@
+-- | Convert Pandoc to rich text format.
+module Text.Pandoc.Writers.RTF (
+ writeRTF
+ ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared
+import List ( isSuffixOf )
+import Char ( ord, chr )
+
+-- | Convert Pandoc to a string in rich text format.
+writeRTF :: WriterOptions -> Pandoc -> String
+writeRTF options (Pandoc meta blocks) =
+ let notes = filter isNoteBlock blocks in -- assumes all notes are at outer level
+ let head = if writerStandalone options then
+ rtfHeader notes (writerHeader options) meta
+ else
+ ""
+ foot = if writerStandalone options then "\n}\n" else ""
+ body = (writerIncludeBefore options) ++
+ (concatMap (blockToRTF notes 0) (replaceReferenceLinks blocks)) ++
+ (writerIncludeAfter options) in
+ head ++ body ++ foot
+
+-- | Convert unicode characters (> 127) into rich text format representation.
+handleUnicode :: String -> String
+handleUnicode [] = []
+handleUnicode (c:cs) = if (ord c) > 127 then
+ '\\':'u':(show (ord c)) ++ "?" ++ (handleUnicode cs)
+ else
+ c:(handleUnicode cs)
+
+escapeSpecial = backslashEscape "{\\}"
+escapeTab = gsub "\\\\t" "\\\\tab "
+
+-- | Escape strings as needed for rich text format.
+stringToRTF :: String -> String
+stringToRTF = handleUnicode . escapeSpecial . escapeTab
+
+-- | Escape raw LaTeX strings for RTF. Don't escape \t; it might
+-- be the first letter of a command!
+latexStringToRTF :: String -> String
+latexStringToRTF = handleUnicode . escapeSpecial
+
+-- | Escape things as needed for code block in RTF.
+codeStringToRTF :: String -> String
+codeStringToRTF str = joinWithSep "\\line\n" (lines (stringToRTF str))
+
+-- | Deal with raw LaTeX.
+latexToRTF :: String -> String
+latexToRTF str = "{\\cf1 " ++ (latexStringToRTF str) ++ "\\cf0 } "
+
+-- | Make a paragraph with first-line indent, block indent, and space after.
+rtfParSpaced :: Int -- ^ space after (in twips)
+ -> Int -- ^ block indent (in twips)
+ -> Int -- ^ first line indent (relative to block) (in twips)
+ -> String -- ^ string with content
+ -> String
+rtfParSpaced spaceAfter indent firstLineIndent content =
+ "{\\pard \\sa" ++ (show spaceAfter) ++ " \\li" ++ (show indent) ++
+ " \\fi" ++ (show firstLineIndent) ++ " " ++ content ++ "\\par}\n"
+
+-- | Default paragraph.
+rtfPar :: Int -- ^ block indent (in twips)
+ -> Int -- ^ first line indent (relative to block) (in twips)
+ -> String -- ^ string with content
+ -> String
+rtfPar = rtfParSpaced 180
+
+-- | Compact paragraph (e.g. for compact list items).
+rtfCompact :: Int -- ^ block indent (in twips)
+ -> Int -- ^ first line indent (relative to block) (in twips)
+ -> String -- ^ string with content
+ -> String
+rtfCompact = rtfParSpaced 0
+
+-- number of twips to indent
+indentIncrement = 720
+listIncrement = 360
+
+-- | Returns appropriate bullet list marker for indent level.
+bulletMarker :: Int -> String
+bulletMarker indent = case (indent `mod` 720) of
+ 0 -> "\\bullet "
+ otherwise -> "\\endash "
+
+-- | Returns appropriate (list of) ordered list markers for indent level.
+orderedMarkers :: Int -> [String]
+orderedMarkers indent = case (indent `mod` 720) of
+ 0 -> map (\x -> show x ++ ".") [1..]
+ otherwise -> map (\x -> show x ++ ".") $ cycle ['a'..'z']
+
+-- | Returns RTF header.
+rtfHeader :: [Block] -- ^ list of note blocks
+ -> String -- ^ header text
+ -> Meta -- ^ bibliographic information
+ -> String
+rtfHeader notes headerText (Meta title authors date) =
+ let titletext = if null title then
+ ""
+ else
+ rtfPar 0 0 ("\\qc \\b \\fs36 " ++ inlineListToRTF notes title)
+ authorstext = if null authors then
+ ""
+ else
+ rtfPar 0 0 ("\\qc " ++ (joinWithSep "\\" (map stringToRTF authors)))
+ datetext = if date == "" then "" else rtfPar 0 0 ("\\qc " ++ stringToRTF date) in
+ let spacer = if null (titletext ++ authorstext ++ datetext) then "" else rtfPar 0 0 "" in
+ headerText ++ titletext ++ authorstext ++ datetext ++ spacer
+
+-- | Convert Pandoc block element to RTF.
+blockToRTF :: [Block] -- ^ list of note blocks
+ -> Int -- ^ indent level
+ -> Block -- ^ block to convert
+ -> String
+blockToRTF notes indent Blank = rtfPar indent 0 ""
+blockToRTF notes indent Null = ""
+blockToRTF notes indent (Plain lst) = rtfCompact indent 0 (inlineListToRTF notes lst)
+blockToRTF notes indent (Para lst) = rtfPar indent 0 (inlineListToRTF notes lst)
+blockToRTF notes indent (BlockQuote lst) =
+ concatMap (blockToRTF notes (indent + indentIncrement)) lst
+blockToRTF notes indent (Note ref lst) = "" -- there shouldn't be any after filtering
+blockToRTF notes indent (Key _ _) = ""
+blockToRTF notes indent (CodeBlock str) = rtfPar indent 0 ("\\f1 " ++ (codeStringToRTF str))
+blockToRTF notes indent (RawHtml str) = ""
+blockToRTF notes indent (BulletList lst) =
+ spaceAtEnd $ concatMap (listItemToRTF notes indent (bulletMarker indent)) lst
+blockToRTF notes indent (OrderedList lst) =
+ spaceAtEnd $ concat $ zipWith (listItemToRTF notes indent) (orderedMarkers indent) lst
+blockToRTF notes indent HorizontalRule =
+ rtfPar indent 0 "\\qc \\emdash\\emdash\\emdash\\emdash\\emdash"
+blockToRTF notes indent (Header level lst) =
+ rtfPar indent 0 ("\\b \\fs" ++ (show (40 - (level * 4))) ++ " " ++
+ (inlineListToRTF notes lst))
+
+-- | Ensure that there's the same amount of space after compact
+-- lists as after regular lists.
+spaceAtEnd :: String -> String
+spaceAtEnd str =
+ if isSuffixOf "\\par}\n" str then
+ (take ((length str) - 6) str) ++ "\\sa180\\par}\n"
+ else
+ str
+
+-- | Convert list item (list of blocks) to RTF.
+listItemToRTF :: [Block] -- ^ list of note blocks
+ -> Int -- ^ indent level
+ -> String -- ^ list start marker
+ -> [Block] -- ^ list item (list of blocks)
+ -> [Char]
+listItemToRTF notes indent marker [] =
+ rtfCompact (indent + listIncrement) (0 - listIncrement)
+ (marker ++ "\\tx" ++ (show listIncrement) ++ "\\tab ")
+listItemToRTF notes indent marker list =
+ let (first:rest) = map (blockToRTF notes (indent + listIncrement)) list in
+ let modFirst = gsub "\\\\fi-?[0-9]+" ("\\\\fi" ++ (show (0 - listIncrement)) ++
+ " " ++ marker ++ "\\\\tx" ++ (show listIncrement) ++ "\\\\tab") first in
+ modFirst ++ (concat rest)
+
+-- | Convert list of inline items to RTF.
+inlineListToRTF :: [Block] -- ^ list of note blocks
+ -> [Inline] -- ^ list of inlines to convert
+ -> String
+inlineListToRTF notes lst = concatMap (inlineToRTF notes) lst
+
+-- | Convert inline item to RTF.
+inlineToRTF :: [Block] -- ^ list of note blocks
+ -> Inline -- ^ inline to convert
+ -> String
+inlineToRTF notes (Emph lst) = "{\\i " ++ (inlineListToRTF notes lst) ++ "} "
+inlineToRTF notes (Strong lst) = "{\\b " ++ (inlineListToRTF notes lst) ++ "} "
+inlineToRTF notes (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "} "
+inlineToRTF notes (Str str) = stringToRTF str
+inlineToRTF notes (TeX str) = latexToRTF str
+inlineToRTF notes (HtmlInline str) = ""
+inlineToRTF notes (LineBreak) = "\\line "
+inlineToRTF notes Space = " "
+inlineToRTF notes (Link text (Src src tit)) =
+ "{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++ "\"}}{\\fldrslt{\\ul\n"
+ ++ (inlineListToRTF notes text) ++ "\n}}}\n"
+inlineToRTF notes (Link text (Ref [])) = "[" ++ (inlineListToRTF notes text) ++ "]"
+inlineToRTF notes (Link text (Ref ref)) = "[" ++ (inlineListToRTF notes text) ++ "][" ++
+ (inlineListToRTF notes ref) ++ "]" -- this is what markdown does, for better or worse
+inlineToRTF notes (Image alternate (Src source tit)) = "{\\cf1 [image: " ++ source ++ "]\\cf0}"
+inlineToRTF notes (Image alternate (Ref [])) = "![" ++ (inlineListToRTF notes alternate) ++ "]"
+inlineToRTF notes (Image alternate (Ref ref)) = "![" ++ (inlineListToRTF notes alternate) ++
+ "][" ++ (inlineListToRTF notes ref) ++ "]"
+inlineToRTF [] (NoteRef ref) = ""
+inlineToRTF ((Note firstref firstblocks):rest) (NoteRef ref) =
+ if firstref == ref then
+ "{\\super\\chftn}{\\*\\footnote\\chftn\\~\\plain\\pard " ++
+ (concatMap (blockToRTF rest 0) firstblocks) ++ "}"
+ else
+ inlineToRTF rest (NoteRef ref)
+
diff --git a/src/Text/Pandoc/Writers/S5.hs b/src/Text/Pandoc/Writers/S5.hs
new file mode 100644
index 000000000..2d0b913a3
--- /dev/null
+++ b/src/Text/Pandoc/Writers/S5.hs
@@ -0,0 +1,95 @@
+----------------------------------------------------
+-- Do not edit this file by hand. Edit
+-- 'templates/S5.hs'
+-- and run ./fillTemplates.pl Text/Pandoc/Writers/S5.hs
+----------------------------------------------------
+
+-- | Definitions for creation of S5 powerpoint-like HTML.
+-- (See <http://meyerweb.com/eric/tools/s5/>.)
+module Text.Pandoc.Writers.S5 (
+ -- * Strings
+ s5Javascript,
+ s5CSS,
+ s5Links,
+ -- * Functions
+ writeS5,
+ insertS5Structure
+ ) where
+import Text.Pandoc.Shared ( joinWithSep, WriterOptions )
+import Text.Pandoc.Writers.HTML ( writeHtml )
+import Text.Pandoc.Definition
+
+s5Javascript :: String
+s5Javascript = "<script type=\"text/javascript\">\n// S5 v1.1 slides.js -- released into the Public Domain\n//\n// Please see http://www.meyerweb.com/eric/tools/s5/credits.html for information \n// about all the wonderful and talented contributors to this code!\n\nvar undef;\nvar slideCSS = '';\nvar snum = 0;\nvar smax = 1;\nvar incpos = 0;\nvar number = undef;\nvar s5mode = true;\nvar defaultView = 'slideshow';\nvar controlVis = 'visible';\n\nvar isIE = navigator.appName == 'Microsoft Internet Explorer' && navigator.userAgent.indexOf('Opera') < 1 ? 1 : 0;\nvar isOp = navigator.userAgent.indexOf('Opera') > -1 ? 1 : 0;\nvar isGe = navigator.userAgent.indexOf('Gecko') > -1 && navigator.userAgent.indexOf('Safari') < 1 ? 1 : 0;\n\nfunction hasClass(object, className) {\n\tif (!object.className) return false;\n\treturn (object.className.search('(^|\\\\s)' + className + '(\\\\s|$)') != -1);\n}\n\nfunction hasValue(object, value) {\n\tif (!object) return false;\n\treturn (object.search('(^|\\\\s)' + value + '(\\\\s|$)') != -1);\n}\n\nfunction removeClass(object,className) {\n\tif (!object) return;\n\tobject.className = object.className.replace(new RegExp('(^|\\\\s)'+className+'(\\\\s|$)'), RegExp.$1+RegExp.$2);\n}\n\nfunction addClass(object,className) {\n\tif (!object || hasClass(object, className)) return;\n\tif (object.className) {\n\t\tobject.className += ' '+className;\n\t} else {\n\t\tobject.className = className;\n\t}\n}\n\nfunction GetElementsWithClassName(elementName,className) {\n\tvar allElements = document.getElementsByTagName(elementName);\n\tvar elemColl = new Array();\n\tfor (var i = 0; i< allElements.length; i++) {\n\t\tif (hasClass(allElements[i], className)) {\n\t\t\telemColl[elemColl.length] = allElements[i];\n\t\t}\n\t}\n\treturn elemColl;\n}\n\nfunction isParentOrSelf(element, id) {\n\tif (element == null || element.nodeName=='BODY') return false;\n\telse if (element.id == id) return true;\n\telse return isParentOrSelf(element.parentNode, id);\n}\n\nfunction nodeValue(node) {\n\tvar result = \"\";\n\tif (node.nodeType == 1) {\n\t\tvar children = node.childNodes;\n\t\tfor (var i = 0; i < children.length; ++i) {\n\t\t\tresult += nodeValue(children[i]);\n\t\t}\t\t\n\t}\n\telse if (node.nodeType == 3) {\n\t\tresult = node.nodeValue;\n\t}\n\treturn(result);\n}\n\nfunction slideLabel() {\n\tvar slideColl = GetElementsWithClassName('*','slide');\n\tvar list = document.getElementById('jumplist');\n\tsmax = slideColl.length;\n\tfor (var n = 0; n < smax; n++) {\n\t\tvar obj = slideColl[n];\n\n\t\tvar did = 'slide' + n.toString();\n\t\tobj.setAttribute('id',did);\n\t\tif (isOp) continue;\n\n\t\tvar otext = '';\n\t\tvar menu = obj.firstChild;\n\t\tif (!menu) continue; // to cope with empty slides\n\t\twhile (menu && menu.nodeType == 3) {\n\t\t\tmenu = menu.nextSibling;\n\t\t}\n\t \tif (!menu) continue; // to cope with slides with only text nodes\n\n\t\tvar menunodes = menu.childNodes;\n\t\tfor (var o = 0; o < menunodes.length; o++) {\n\t\t\totext += nodeValue(menunodes[o]);\n\t\t}\n\t\tlist.options[list.length] = new Option(n + ' : ' + otext, n);\n\t}\n}\n\nfunction currentSlide() {\n\tvar cs;\n\tif (document.getElementById) {\n\t\tcs = document.getElementById('currentSlide');\n\t} else {\n\t\tcs = document.currentSlide;\n\t}\n\tcs.innerHTML = '<span id=\"csHere\">' + snum + '<\\/span> ' + \n\t\t'<span id=\"csSep\">\\/<\\/span> ' + \n\t\t'<span id=\"csTotal\">' + (smax-1) + '<\\/span>';\n\tif (snum == 0) {\n\t\tcs.style.visibility = 'hidden';\n\t} else {\n\t\tcs.style.visibility = 'visible';\n\t}\n}\n\nfunction go(step) {\n\tif (document.getElementById('slideProj').disabled || step == 0) return;\n\tvar jl = document.getElementById('jumplist');\n\tvar cid = 'slide' + snum;\n\tvar ce = document.getElementById(cid);\n\tif (incrementals[snum].length > 0) {\n\t\tfor (var i = 0; i < incrementals[snum].length; i++) {\n\t\t\tremoveClass(incrementals[snum][i], 'current');\n\t\t\tremoveClass(incrementals[snum][i], 'incremental');\n\t\t}\n\t}\n\tif (step != 'j') {\n\t\tsnum += step;\n\t\tlmax = smax - 1;\n\t\tif (snum > lmax) snum = lmax;\n\t\tif (snum < 0) snum = 0;\n\t} else\n\t\tsnum = parseInt(jl.value);\n\tvar nid = 'slide' + snum;\n\tvar ne = document.getElementById(nid);\n\tif (!ne) {\n\t\tne = document.getElementById('slide0');\n\t\tsnum = 0;\n\t}\n\tif (step < 0) {incpos = incrementals[snum].length} else {incpos = 0;}\n\tif (incrementals[snum].length > 0 && incpos == 0) {\n\t\tfor (var i = 0; i < incrementals[snum].length; i++) {\n\t\t\tif (hasClass(incrementals[snum][i], 'current'))\n\t\t\t\tincpos = i + 1;\n\t\t\telse\n\t\t\t\taddClass(incrementals[snum][i], 'incremental');\n\t\t}\n\t}\n\tif (incrementals[snum].length > 0 && incpos > 0)\n\t\taddClass(incrementals[snum][incpos - 1], 'current');\n\tce.style.visibility = 'hidden';\n\tne.style.visibility = 'visible';\n\tjl.selectedIndex = snum;\n\tcurrentSlide();\n\tnumber = 0;\n}\n\nfunction goTo(target) {\n\tif (target >= smax || target == snum) return;\n\tgo(target - snum);\n}\n\nfunction subgo(step) {\n\tif (step > 0) {\n\t\tremoveClass(incrementals[snum][incpos - 1],'current');\n\t\tremoveClass(incrementals[snum][incpos], 'incremental');\n\t\taddClass(incrementals[snum][incpos],'current');\n\t\tincpos++;\n\t} else {\n\t\tincpos--;\n\t\tremoveClass(incrementals[snum][incpos],'current');\n\t\taddClass(incrementals[snum][incpos], 'incremental');\n\t\taddClass(incrementals[snum][incpos - 1],'current');\n\t}\n}\n\nfunction toggle() {\n\tvar slideColl = GetElementsWithClassName('*','slide');\n\tvar slides = document.getElementById('slideProj');\n\tvar outline = document.getElementById('outlineStyle');\n\tif (!slides.disabled) {\n\t\tslides.disabled = true;\n\t\toutline.disabled = false;\n\t\ts5mode = false;\n\t\tfontSize('1em');\n\t\tfor (var n = 0; n < smax; n++) {\n\t\t\tvar slide = slideColl[n];\n\t\t\tslide.style.visibility = 'visible';\n\t\t}\n\t} else {\n\t\tslides.disabled = false;\n\t\toutline.disabled = true;\n\t\ts5mode = true;\n\t\tfontScale();\n\t\tfor (var n = 0; n < smax; n++) {\n\t\t\tvar slide = slideColl[n];\n\t\t\tslide.style.visibility = 'hidden';\n\t\t}\n\t\tslideColl[snum].style.visibility = 'visible';\n\t}\n}\n\nfunction showHide(action) {\n\tvar obj = GetElementsWithClassName('*','hideme')[0];\n\tswitch (action) {\n\tcase 's': obj.style.visibility = 'visible'; break;\n\tcase 'h': obj.style.visibility = 'hidden'; break;\n\tcase 'k':\n\t\tif (obj.style.visibility != 'visible') {\n\t\t\tobj.style.visibility = 'visible';\n\t\t} else {\n\t\t\tobj.style.visibility = 'hidden';\n\t\t}\n\tbreak;\n\t}\n}\n\n// 'keys' code adapted from MozPoint (http://mozpoint.mozdev.org/)\nfunction keys(key) {\n\tif (!key) {\n\t\tkey = event;\n\t\tkey.which = key.keyCode;\n\t}\n\tif (key.which == 84) {\n\t\ttoggle();\n\t\treturn;\n\t}\n\tif (s5mode) {\n\t\tswitch (key.which) {\n\t\t\tcase 10: // return\n\t\t\tcase 13: // enter\n\t\t\t\tif (window.event && isParentOrSelf(window.event.srcElement, 'controls')) return;\n\t\t\t\tif (key.target && isParentOrSelf(key.target, 'controls')) return;\n\t\t\t\tif(number != undef) {\n\t\t\t\t\tgoTo(number);\n\t\t\t\t\tbreak;\n\t\t\t\t}\n\t\t\tcase 32: // spacebar\n\t\t\tcase 34: // page down\n\t\t\tcase 39: // rightkey\n\t\t\tcase 40: // downkey\n\t\t\t\tif(number != undef) {\n\t\t\t\t\tgo(number);\n\t\t\t\t} else if (!incrementals[snum] || incpos >= incrementals[snum].length) {\n\t\t\t\t\tgo(1);\n\t\t\t\t} else {\n\t\t\t\t\tsubgo(1);\n\t\t\t\t}\n\t\t\t\tbreak;\n\t\t\tcase 33: // page up\n\t\t\tcase 37: // leftkey\n\t\t\tcase 38: // upkey\n\t\t\t\tif(number != undef) {\n\t\t\t\t\tgo(-1 * number);\n\t\t\t\t} else if (!incrementals[snum] || incpos <= 0) {\n\t\t\t\t\tgo(-1);\n\t\t\t\t} else {\n\t\t\t\t\tsubgo(-1);\n\t\t\t\t}\n\t\t\t\tbreak;\n\t\t\tcase 36: // home\n\t\t\t\tgoTo(0);\n\t\t\t\tbreak;\n\t\t\tcase 35: // end\n\t\t\t\tgoTo(smax-1);\n\t\t\t\tbreak;\n\t\t\tcase 67: // c\n\t\t\t\tshowHide('k');\n\t\t\t\tbreak;\n\t\t}\n\t\tif (key.which < 48 || key.which > 57) {\n\t\t\tnumber = undef;\n\t\t} else {\n\t\t\tif (window.event && isParentOrSelf(window.event.srcElement, 'controls')) return;\n\t\t\tif (key.target && isParentOrSelf(key.target, 'controls')) return;\n\t\t\tnumber = (((number != undef) ? number : 0) * 10) + (key.which - 48);\n\t\t}\n\t}\n\treturn false;\n}\n\nfunction clicker(e) {\n\tnumber = undef;\n\tvar target;\n\tif (window.event) {\n\t\ttarget = window.event.srcElement;\n\t\te = window.event;\n\t} else target = e.target;\n\tif (target.getAttribute('href') != null || hasValue(target.rel, 'external') || isParentOrSelf(target, 'controls') || isParentOrSelf(target,'embed') || isParentOrSelf(target,'object')) return true;\n\tif (!e.which || e.which == 1) {\n\t\tif (!incrementals[snum] || incpos >= incrementals[snum].length) {\n\t\t\tgo(1);\n\t\t} else {\n\t\t\tsubgo(1);\n\t\t}\n\t}\n}\n\nfunction findSlide(hash) {\n\tvar target = null;\n\tvar slides = GetElementsWithClassName('*','slide');\n\tfor (var i = 0; i < slides.length; i++) {\n\t\tvar targetSlide = slides[i];\n\t\tif ( (targetSlide.name && targetSlide.name == hash)\n\t\t || (targetSlide.id && targetSlide.id == hash) ) {\n\t\t\ttarget = targetSlide;\n\t\t\tbreak;\n\t\t}\n\t}\n\twhile(target != null && target.nodeName != 'BODY') {\n\t\tif (hasClass(target, 'slide')) {\n\t\t\treturn parseInt(target.id.slice(5));\n\t\t}\n\t\ttarget = target.parentNode;\n\t}\n\treturn null;\n}\n\nfunction slideJump() {\n\tif (window.location.hash == null) return;\n\tvar sregex = /^#slide(\\d+)$/;\n\tvar matches = sregex.exec(window.location.hash);\n\tvar dest = null;\n\tif (matches != null) {\n\t\tdest = parseInt(matches[1]);\n\t} else {\n\t\tdest = findSlide(window.location.hash.slice(1));\n\t}\n\tif (dest != null)\n\t\tgo(dest - snum);\n}\n\nfunction fixLinks() {\n\tvar thisUri = window.location.href;\n\tthisUri = thisUri.slice(0, thisUri.length - window.location.hash.length);\n\tvar aelements = document.getElementsByTagName('A');\n\tfor (var i = 0; i < aelements.length; i++) {\n\t\tvar a = aelements[i].href;\n\t\tvar slideID = a.match('\\#slide[0-9]{1,2}');\n\t\tif ((slideID) && (slideID[0].slice(0,1) == '#')) {\n\t\t\tvar dest = findSlide(slideID[0].slice(1));\n\t\t\tif (dest != null) {\n\t\t\t\tif (aelements[i].addEventListener) {\n\t\t\t\t\taelements[i].addEventListener(\"click\", new Function(\"e\",\n\t\t\t\t\t\t\"if (document.getElementById('slideProj').disabled) return;\" +\n\t\t\t\t\t\t\"go(\"+dest+\" - snum); \" +\n\t\t\t\t\t\t\"if (e.preventDefault) e.preventDefault();\"), true);\n\t\t\t\t} else if (aelements[i].attachEvent) {\n\t\t\t\t\taelements[i].attachEvent(\"onclick\", new Function(\"\",\n\t\t\t\t\t\t\"if (document.getElementById('slideProj').disabled) return;\" +\n\t\t\t\t\t\t\"go(\"+dest+\" - snum); \" +\n\t\t\t\t\t\t\"event.returnValue = false;\"));\n\t\t\t\t}\n\t\t\t}\n\t\t}\n\t}\n}\n\nfunction externalLinks() {\n\tif (!document.getElementsByTagName) return;\n\tvar anchors = document.getElementsByTagName('a');\n\tfor (var i=0; i<anchors.length; i++) {\n\t\tvar anchor = anchors[i];\n\t\tif (anchor.getAttribute('href') && hasValue(anchor.rel, 'external')) {\n\t\t\tanchor.target = '_blank';\n\t\t\taddClass(anchor,'external');\n\t\t}\n\t}\n}\n\nfunction createControls() {\n\tvar controlsDiv = document.getElementById(\"controls\");\n\tif (!controlsDiv) return;\n\tvar hider = ' onmouseover=\"showHide(\\'s\\');\" onmouseout=\"showHide(\\'h\\');\"';\n\tvar hideDiv, hideList = '';\n\tif (controlVis == 'hidden') {\n\t\thideDiv = hider;\n\t} else {\n\t\thideList = hider;\n\t}\n\tcontrolsDiv.innerHTML = '<form action=\"#\" id=\"controlForm\"' + hideDiv + '>' +\n\t'<div id=\"navLinks\">' +\n\t'<a accesskey=\"t\" id=\"toggle\" href=\"javascript:toggle();\">&#216;<\\/a>' +\n\t'<a accesskey=\"z\" id=\"prev\" href=\"javascript:go(-1);\">&laquo;<\\/a>' +\n\t'<a accesskey=\"x\" id=\"next\" href=\"javascript:go(1);\">&raquo;<\\/a>' +\n\t'<div id=\"navList\"' + hideList + '><select id=\"jumplist\" onchange=\"go(\\'j\\');\"><\\/select><\\/div>' +\n\t'<\\/div><\\/form>';\n\tif (controlVis == 'hidden') {\n\t\tvar hidden = document.getElementById('navLinks');\n\t} else {\n\t\tvar hidden = document.getElementById('jumplist');\n\t}\n\taddClass(hidden,'hideme');\n}\n\nfunction fontScale() { // causes layout problems in FireFox that get fixed if browser's Reload is used; same may be true of other Gecko-based browsers\n\tif (!s5mode) return false;\n\tvar vScale = 22; // both yield 32 (after rounding) at 1024x768\n\tvar hScale = 32; // perhaps should auto-calculate based on theme's declared value?\n\tif (window.innerHeight) {\n\t\tvar vSize = window.innerHeight;\n\t\tvar hSize = window.innerWidth;\n\t} else if (document.documentElement.clientHeight) {\n\t\tvar vSize = document.documentElement.clientHeight;\n\t\tvar hSize = document.documentElement.clientWidth;\n\t} else if (document.body.clientHeight) {\n\t\tvar vSize = document.body.clientHeight;\n\t\tvar hSize = document.body.clientWidth;\n\t} else {\n\t\tvar vSize = 700; // assuming 1024x768, minus chrome and such\n\t\tvar hSize = 1024; // these do not account for kiosk mode or Opera Show\n\t}\n\tvar newSize = Math.min(Math.round(vSize/vScale),Math.round(hSize/hScale));\n\tfontSize(newSize + 'px');\n\tif (isGe) { // hack to counter incremental reflow bugs\n\t\tvar obj = document.getElementsByTagName('body')[0];\n\t\tobj.style.display = 'none';\n\t\tobj.style.display = 'block';\n\t}\n}\n\nfunction fontSize(value) {\n\tif (!(s5ss = document.getElementById('s5ss'))) {\n\t\tif (!isIE) {\n\t\t\tdocument.getElementsByTagName('head')[0].appendChild(s5ss = document.createElement('style'));\n\t\t\ts5ss.setAttribute('media','screen, projection');\n\t\t\ts5ss.setAttribute('id','s5ss');\n\t\t} else {\n\t\t\tdocument.createStyleSheet();\n\t\t\tdocument.s5ss = document.styleSheets[document.styleSheets.length - 1];\n\t\t}\n\t}\n\tif (!isIE) {\n\t\twhile (s5ss.lastChild) s5ss.removeChild(s5ss.lastChild);\n\t\ts5ss.appendChild(document.createTextNode('body {font-size: ' + value + ' !important;}'));\n\t} else {\n\t\tdocument.s5ss.addRule('body','font-size: ' + value + ' !important;');\n\t}\n}\n\nfunction notOperaFix() {\n\tslideCSS = document.getElementById('slideProj').href;\n\tvar slides = document.getElementById('slideProj');\n\tvar outline = document.getElementById('outlineStyle');\n\tslides.setAttribute('media','screen');\n\toutline.disabled = true;\n\tif (isGe) {\n\t\tslides.setAttribute('href','null'); // Gecko fix\n\t\tslides.setAttribute('href',slideCSS); // Gecko fix\n\t}\n\tif (isIE && document.styleSheets && document.styleSheets[0]) {\n\t\tdocument.styleSheets[0].addRule('img', 'behavior: url(ui/default/iepngfix.htc)');\n\t\tdocument.styleSheets[0].addRule('div', 'behavior: url(ui/default/iepngfix.htc)');\n\t\tdocument.styleSheets[0].addRule('.slide', 'behavior: url(ui/default/iepngfix.htc)');\n\t}\n}\n\nfunction getIncrementals(obj) {\n\tvar incrementals = new Array();\n\tif (!obj) \n\t\treturn incrementals;\n\tvar children = obj.childNodes;\n\tfor (var i = 0; i < children.length; i++) {\n\t\tvar child = children[i];\n\t\tif (hasClass(child, 'incremental')) {\n\t\t\tif (child.nodeName == 'OL' || child.nodeName == 'UL') {\n\t\t\t\tremoveClass(child, 'incremental');\n\t\t\t\tfor (var j = 0; j < child.childNodes.length; j++) {\n\t\t\t\t\tif (child.childNodes[j].nodeType == 1) {\n\t\t\t\t\t\taddClass(child.childNodes[j], 'incremental');\n\t\t\t\t\t}\n\t\t\t\t}\n\t\t\t} else {\n\t\t\t\tincrementals[incrementals.length] = child;\n\t\t\t\tremoveClass(child,'incremental');\n\t\t\t}\n\t\t}\n\t\tif (hasClass(child, 'show-first')) {\n\t\t\tif (child.nodeName == 'OL' || child.nodeName == 'UL') {\n\t\t\t\tremoveClass(child, 'show-first');\n\t\t\t\tif (child.childNodes[isGe].nodeType == 1) {\n\t\t\t\t\tremoveClass(child.childNodes[isGe], 'incremental');\n\t\t\t\t}\n\t\t\t} else {\n\t\t\t\tincrementals[incrementals.length] = child;\n\t\t\t}\n\t\t}\n\t\tincrementals = incrementals.concat(getIncrementals(child));\n\t}\n\treturn incrementals;\n}\n\nfunction createIncrementals() {\n\tvar incrementals = new Array();\n\tfor (var i = 0; i < smax; i++) {\n\t\tincrementals[i] = getIncrementals(document.getElementById('slide'+i));\n\t}\n\treturn incrementals;\n}\n\nfunction defaultCheck() {\n\tvar allMetas = document.getElementsByTagName('meta');\n\tfor (var i = 0; i< allMetas.length; i++) {\n\t\tif (allMetas[i].name == 'defaultView') {\n\t\t\tdefaultView = allMetas[i].content;\n\t\t}\n\t\tif (allMetas[i].name == 'controlVis') {\n\t\t\tcontrolVis = allMetas[i].content;\n\t\t}\n\t}\n}\n\n// Key trap fix, new function body for trap()\nfunction trap(e) {\n\tif (!e) {\n\t\te = event;\n\t\te.which = e.keyCode;\n\t}\n\ttry {\n\t\tmodifierKey = e.ctrlKey || e.altKey || e.metaKey;\n\t}\n\tcatch(e) {\n\t\tmodifierKey = false;\n\t}\n\treturn modifierKey || e.which == 0;\n}\n\nfunction startup() {\n\tdefaultCheck();\n\tif (!isOp) \n\t\tcreateControls();\n\tslideLabel();\n\tfixLinks();\n\texternalLinks();\n\tfontScale();\n\tif (!isOp) {\n\t\tnotOperaFix();\n\t\tincrementals = createIncrementals();\n\t\tslideJump();\n\t\tif (defaultView == 'outline') {\n\t\t\ttoggle();\n\t\t}\n\t\tdocument.onkeyup = keys;\n\t\tdocument.onkeypress = trap;\n\t\tdocument.onclick = clicker;\n\t}\n}\n\nwindow.onload = startup;\nwindow.onresize = function(){setTimeout('fontScale()', 50);}</script>\n"
+
+s5CoreCSS :: String
+s5CoreCSS = "/* Do not edit or override these styles! The system will likely break if you do. */\n\ndiv#header, div#footer, div#controls, .slide {position: absolute;}\nhtml>body div#header, html>body div#footer, \n html>body div#controls, html>body .slide {position: fixed;}\n.handout {display: none;}\n.layout {display: block;}\n.slide, .hideme, .incremental {visibility: hidden;}\n#slide0 {visibility: visible;}\n"
+
+s5FramingCSS :: String
+s5FramingCSS = "/* The following styles size, place, and layer the slide components.\n Edit these if you want to change the overall slide layout.\n The commented lines can be uncommented (and modified, if necessary) \n to help you with the rearrangement process. */\n\n/* target = 1024x768 */\n\ndiv#header, div#footer, .slide {width: 100%; top: 0; left: 0;}\ndiv#header {top: 0; height: 3em; z-index: 1;}\ndiv#footer {top: auto; bottom: 0; height: 2.5em; z-index: 5;}\n.slide {top: 0; width: 92%; padding: 3.5em 4% 4%; z-index: 2; list-style: none;}\ndiv#controls {left: 50%; bottom: 0; width: 50%; z-index: 100;}\ndiv#controls form {position: absolute; bottom: 0; right: 0; width: 100%;\n margin: 0;}\n#currentSlide {position: absolute; width: 10%; left: 45%; bottom: 1em; z-index: 10;}\nhtml>body #currentSlide {position: fixed;}\n\n/*\ndiv#header {background: #FCC;}\ndiv#footer {background: #CCF;}\ndiv#controls {background: #BBD;}\ndiv#currentSlide {background: #FFC;}\n*/\n"
+
+s5PrettyCSS :: String
+s5PrettyCSS = "/* Following are the presentation styles -- edit away! */\n\nbody {background: #FFF url(bodybg.gif) -16px 0 no-repeat; color: #000; font-size: 2em;}\n:link, :visited {text-decoration: none; color: #00C;}\n#controls :active {color: #88A !important;}\n#controls :focus {outline: 1px dotted #227;}\nh1, h2, h3, h4 {font-size: 100%; margin: 0; padding: 0; font-weight: inherit;}\nul, pre {margin: 0; line-height: 1em;}\nhtml, body {margin: 0; padding: 0;}\n\nblockquote, q {font-style: italic;}\nblockquote {padding: 0 2em 0.5em; margin: 0 1.5em 0.5em; text-align: center; font-size: 1em;}\nblockquote p {margin: 0;}\nblockquote i {font-style: normal;}\nblockquote b {display: block; margin-top: 0.5em; font-weight: normal; font-size: smaller; font-style: normal;}\nblockquote b i {font-style: italic;}\n\nkbd {font-weight: bold; font-size: 1em;}\nsup {font-size: smaller; line-height: 1px;}\n\n.slide code {padding: 2px 0.25em; font-weight: bold; color: #533;}\n.slide code.bad, code del {color: red;}\n.slide code.old {color: silver;}\n.slide pre {padding: 0; margin: 0.25em 0 0.5em 0.5em; color: #533; font-size: 90%;}\n.slide pre code {display: block;}\n.slide ul {margin-left: 5%; margin-right: 7%; list-style: disc;}\n.slide li {margin-top: 0.75em; margin-right: 0;}\n.slide ul ul {line-height: 1;}\n.slide ul ul li {margin: .2em; font-size: 85%; list-style: square;}\n.slide img.leader {display: block; margin: 0 auto;}\n\ndiv#header, div#footer {background: #005; color: #AAB;\n font-family: Verdana, Helvetica, sans-serif;}\ndiv#header {background: #005 url(bodybg.gif) -16px 0 no-repeat;\n line-height: 1px;}\ndiv#footer {font-size: 0.5em; font-weight: bold; padding: 1em 0;}\n#footer h1, #footer h2 {display: block; padding: 0 1em;}\n#footer h2 {font-style: italic;}\n\ndiv.long {font-size: 0.75em;}\n.slide h1 {position: absolute; top: 0.7em; left: 87px; z-index: 1;\n margin: 0; padding: 0.3em 0 0 50px; white-space: nowrap;\n font: bold 150%/1em Helvetica, sans-serif; text-transform: capitalize;\n color: #DDE; background: #005;}\n.slide h3 {font-size: 130%;}\nh1 abbr {font-variant: small-caps;}\n\ndiv#controls {position: absolute; left: 50%; bottom: 0;\n width: 50%;\n text-align: right; font: bold 0.9em Verdana, Helvetica, sans-serif;}\nhtml>body div#controls {position: fixed; padding: 0 0 1em 0;\n top: auto;}\ndiv#controls form {position: absolute; bottom: 0; right: 0; width: 100%;\n margin: 0; padding: 0;}\n#controls #navLinks a {padding: 0; margin: 0 0.5em; \n background: #005; border: none; color: #779; \n cursor: pointer;}\n#controls #navList {height: 1em;}\n#controls #navList #jumplist {position: absolute; bottom: 0; right: 0; background: #DDD; color: #227;}\n\n#currentSlide {text-align: center; font-size: 0.5em; color: #449;}\n\n#slide0 {padding-top: 3.5em; font-size: 90%;}\n#slide0 h1 {position: static; margin: 1em 0 0; padding: 0;\n font: bold 2em Helvetica, sans-serif; white-space: normal;\n color: #000; background: transparent;}\n#slide0 h2 {font: bold italic 1em Helvetica, sans-serif; margin: 0.25em;}\n#slide0 h3 {margin-top: 1.5em; font-size: 1.5em;}\n#slide0 h4 {margin-top: 0; font-size: 1em;}\n\nul.urls {list-style: none; display: inline; margin: 0;}\n.urls li {display: inline; margin: 0;}\n.note {display: none;}\n.external {border-bottom: 1px dotted gray;}\nhtml>body .external {border-bottom: none;}\n.external:after {content: \" \\274F\"; font-size: smaller; color: #77B;}\n\n.incremental, .incremental *, .incremental *:after {color: #DDE; visibility: visible;}\nimg.incremental {visibility: hidden;}\n.slide .current {color: #B02;}\n\n\n/* diagnostics\n\nli:after {content: \" [\" attr(class) \"]\"; color: #F88;}\n */"
+
+s5OperaCSS :: String
+s5OperaCSS = "/* DO NOT CHANGE THESE unless you really want to break Opera Show */\n.slide {\n\tvisibility: visible !important;\n\tposition: static !important;\n\tpage-break-before: always;\n}\n#slide0 {page-break-before: avoid;}\n"
+
+s5OutlineCSS :: String
+s5OutlineCSS = "/* don't change this unless you want the layout stuff to show up in the outline view! */\n\n.layout div, #footer *, #controlForm * {display: none;}\n#footer, #controls, #controlForm, #navLinks, #toggle {\n display: block; visibility: visible; margin: 0; padding: 0;}\n#toggle {float: right; padding: 0.5em;}\nhtml>body #toggle {position: fixed; top: 0; right: 0;}\n\n/* making the outline look pretty-ish */\n\n#slide0 h1, #slide0 h2, #slide0 h3, #slide0 h4 {border: none; margin: 0;}\n#slide0 h1 {padding-top: 1.5em;}\n.slide h1 {margin: 1.5em 0 0; padding-top: 0.25em;\n border-top: 1px solid #888; border-bottom: 1px solid #AAA;}\n#toggle {border: 1px solid; border-width: 0 0 1px 1px; background: #FFF;}\n"
+
+s5PrintCSS :: String
+s5PrintCSS = "/* The following rule is necessary to have all slides appear in print! DO NOT REMOVE IT! */ .slide, ul {page-break-inside: avoid; visibility: visible !important;} h1 {page-break-after: avoid;} body {font-size: 12pt; background: white;} * {color: black;} #slide0 h1 {font-size: 200%; border: none; margin: 0.5em 0 0.25em;} #slide0 h3 {margin: 0; padding: 0;} #slide0 h4 {margin: 0 0 0.5em; padding: 0;} #slide0 {margin-bottom: 3em;} h1 {border-top: 2pt solid gray; border-bottom: 1px dotted silver;} .extra {background: transparent !important;} div.extra, pre.extra, .example {font-size: 10pt; color: #333;} ul.extra a {font-weight: bold;} p.example {display: none;} #header {display: none;} #footer h1 {margin: 0; border-bottom: 1px solid; color: gray; font-style: italic;} #footer h2, #controls {display: none;} /* The following rule keeps the layout stuff out of print. Remove at your own risk! */ .layout, .layout * {display: none !important;} "
+
+s5CSS :: String
+s5CSS = "<style type=\"text/css\" media=\"projection\" id=\"slideProj\">\n" ++ s5CoreCSS ++ "\n" ++ s5FramingCSS ++ "\n" ++ s5PrettyCSS ++ "\n</style>\n<style type=\"text/css\" media=\"projection\" id=\"operaFix\">\n" ++ s5OperaCSS ++ "\n</style>\n<style type=\"text/css\" media=\"screen\" id=\"outlineStyle\">\n" ++ s5OutlineCSS ++ "\n</style>\n<style type=\"text/css\" media=\"print\" id=\"slidePrint\">\n" ++ s5PrintCSS ++ "\n</style>\n"
+
+s5Links :: String
+s5Links = "<!-- style sheet links -->\n<link rel=\"stylesheet\" href=\"ui/default/slides.css\" type=\"text/css\" media=\"projection\" id=\"slideProj\" />\n<link rel=\"stylesheet\" href=\"ui/default/outline.css\" type=\"text/css\" media=\"screen\" id=\"outlineStyle\" />\n<link rel=\"stylesheet\" href=\"ui/default/print.css\" type=\"text/css\" media=\"print\" id=\"slidePrint\" />\n<link rel=\"stylesheet\" href=\"ui/default/opera.css\" type=\"text/css\" media=\"projection\" id=\"operaFix\" />\n<!-- S5 JS -->\n<script src=\"ui/default/slides.js\" type=\"text/javascript\"></script>\n"
+
+-- | Converts 'Pandoc' to an S5 HTML presentation.
+writeS5 :: WriterOptions -> Pandoc -> String
+writeS5 options = writeHtml 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)
+ -> [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")]
+
+presentationStart = (RawHtml "<div class=\"presentation\">\n\n")
+
+presentationEnd = (RawHtml "</div>\n")
+
+slideStart = (RawHtml "<div class=\"slide\">\n")
+
+slideEnd = (RawHtml "</div>\n")
+
+-- | Returns 'True' if block is a Header 1.
+isH1 :: Block -> Bool
+isH1 (Header 1 _) = True
+isH1 _ = False
+
+-- | Insert HTML around sections to make individual slides.
+insertSlides :: Bool -> [Block] -> [Block]
+insertSlides beginning blocks =
+ let (beforeHead, rest) = break isH1 blocks in
+ if (null rest) then
+ if beginning then
+ beforeHead
+ else
+ beforeHead ++ [slideEnd]
+ else
+ if beginning then
+ beforeHead ++ slideStart:(head rest):(insertSlides False (tail rest))
+ else
+ beforeHead ++ slideEnd:slideStart:(head rest):(insertSlides False (tail rest))
+
+-- | Insert blocks into 'Pandoc' for slide structure.
+insertS5Structure :: Pandoc -> Pandoc
+insertS5Structure (Pandoc meta []) = Pandoc meta []
+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 (joinWithSep ", " authors)]), (Header 4 [Str date]), slideEnd] else [] in
+ let newBlocks = (layoutDiv title date) ++ presentationStart:firstSlide ++ slides ++ [presentationEnd] in
+ Pandoc (Meta title authors date) newBlocks
+