summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2010-12-12 20:09:14 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2010-12-17 13:39:17 -0800
commit543aa28c3895d4dc7d3d659b652237efb41661b0 (patch)
treef3186cc78a5235d0ead022ca0a5abed2c7a5ace0 /src/Text/Pandoc/Writers
parent2a075e9d7a31303efa823f1779c2b32f9fb8a14f (diff)
Added new prettyprinting module.
* Added Text.Pandoc.Pretty. This is better suited for pandoc than the 'pretty' package. One advantage is that we now get proper wrapping; Emph [Inline] is no longer treated as a big unwrappable unit. Previously we only got breaks for spaces at the "outer level." We can also more easily avoid doubled blank lines. Performance is significantly better as well. * Removed Text.Pandoc.Blocks. Text.Pandoc.Pretty allows you to define blocks and concatenate them. * Modified markdown, RST, org readers to use Text.Pandoc.Pretty instead of Text.PrettyPrint.HughesPJ. * Text.Pandoc.Shared: Added writerColumns to WriterOptions. * Markdown, RST, Org writers now break text at writerColumns. * Added --columns command-line option, which sets stColumns and writerColumns. * Table parsing: If the size of the header > stColumns, use the header size as 100% for purposes of calculating relative widths of columns.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs292
-rw-r--r--src/Text/Pandoc/Writers/Org.hs148
-rw-r--r--src/Text/Pandoc/Writers/RST.hs170
3 files changed, 307 insertions, 303 deletions
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 012889552..fe03ff113 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
@@ -33,11 +34,10 @@ module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where
import Text.Pandoc.Definition
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Shared
-import Text.Pandoc.Parsing
-import Text.Pandoc.Blocks
+import Text.Pandoc.Parsing hiding (blankline)
import Text.ParserCombinators.Parsec ( runParser, GenParser )
import Data.List ( group, isPrefixOf, find, intersperse, transpose )
-import Text.PrettyPrint.HughesPJ hiding ( Str )
+import Text.Pandoc.Pretty
import Control.Monad.State
type Notes = [[Block]]
@@ -64,22 +64,21 @@ writePlain opts document =
plainify :: Pandoc -> Pandoc
plainify = processWith go
- where go :: [Inline] -> [Inline]
- go (Emph xs : ys) = go xs ++ go ys
- go (Strong xs : ys) = go xs ++ go ys
- go (Strikeout xs : ys) = go xs ++ go ys
- go (Superscript xs : ys) = go xs ++ go ys
- go (Subscript xs : ys) = go xs ++ go ys
- go (SmallCaps xs : ys) = go xs ++ go ys
- go (Code s : ys) = Str s : go ys
- go (Math _ s : ys) = Str s : go ys
- go (TeX _ : ys) = Str "" : go ys
- go (HtmlInline _ : ys) = Str "" : go ys
- go (Link xs _ : ys) = go xs ++ go ys
- go (Image _ _ : ys) = go ys
- go (Cite _ cits : ys) = go cits ++ go ys
- go (x : ys) = x : go ys
- go [] = []
+ where go :: Inline -> Inline
+ go (Emph xs) = SmallCaps xs
+ go (Strong xs) = SmallCaps xs
+ go (Strikeout xs) = SmallCaps xs
+ go (Superscript xs) = SmallCaps xs
+ go (Subscript xs) = SmallCaps xs
+ go (SmallCaps xs) = SmallCaps xs
+ go (Code s) = Str s
+ go (Math _ s) = Str s
+ go (TeX _) = Str ""
+ go (HtmlInline _) = Str ""
+ go (Link xs _) = SmallCaps xs
+ go (Image xs _) = SmallCaps $ [Str "["] ++ xs ++ [Str "]"]
+ go (Cite _ cits) = SmallCaps cits
+ go x = x
-- | Return markdown representation of document.
pandocToMarkdown :: WriterOptions -> Pandoc -> State WriterState String
@@ -97,15 +96,19 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do
notes' <- notesToMarkdown opts (reverse $ stNotes st)
st' <- get -- note that the notes may contain refs
refs' <- refsToMarkdown opts (reverse $ stRefs st')
- let main = render $ foldl ($+$) empty $ [body, notes', refs']
+ let colwidth = if writerWrapText opts
+ then Just $ writerColumns opts
+ else Nothing
+ let main = render colwidth $ body <>
+ blankline <> notes' <> blankline <> refs'
let context = writerVariables opts ++
- [ ("toc", render toc)
+ [ ("toc", render colwidth toc)
, ("body", main)
- , ("title", render title')
- , ("date", render date')
+ , ("title", render colwidth title')
+ , ("date", render colwidth date')
] ++
[ ("titleblock", "yes") | titleblock ] ++
- [ ("author", render a) | a <- authors' ]
+ [ ("author", render colwidth a) | a <- authors' ]
if writerStandalone opts
then return $ renderTemplate context $ writerTemplate opts
else return main
@@ -113,29 +116,36 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do
-- | Return markdown representation of reference key table.
refsToMarkdown :: WriterOptions -> Refs -> State WriterState Doc
refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat
-
+
-- | Return markdown representation of a reference key.
keyToMarkdown :: WriterOptions
-> ([Inline], (String, String))
-> State WriterState Doc
keyToMarkdown opts (label, (src, tit)) = do
label' <- inlineListToMarkdown opts label
- let tit' = if null tit then empty else text $ " \"" ++ tit ++ "\""
- return $ text " " <> char '[' <> label' <> char ']' <> text ": " <>
- text src <> tit'
+ let tit' = if null tit
+ then empty
+ else space <> "\"" <> text tit <> "\""
+ return $ nest 2 $ hang 2
+ ("[" <> label' <> "]:" <> space) (text src <> tit')
-- | Return markdown representation of notes.
notesToMarkdown :: WriterOptions -> [[Block]] -> State WriterState Doc
notesToMarkdown opts notes =
- mapM (\(num, note) -> noteToMarkdown opts num note) (zip [1..] notes) >>=
- return . vcat
+ mapM (\(num, note) -> noteToMarkdown opts num note) (zip [1..] notes) >>=
+ return . vsep
-- | Return markdown representation of a note.
noteToMarkdown :: WriterOptions -> Int -> [Block] -> State WriterState Doc
noteToMarkdown opts num blocks = do
contents <- blockListToMarkdown opts blocks
- let marker = text "[^" <> text (show num) <> text "]:"
- return $ hang' marker (writerTabStop opts) contents
+ let num' = text $ show num
+ let marker = text "[^" <> num' <> text "]:"
+ let markerSize = 4 + offset num'
+ let spacer = case writerTabStop opts - markerSize of
+ n | n > 0 -> text $ replicate n ' '
+ _ -> text " "
+ return $ hang (writerTabStop opts) (marker <> spacer) contents
-- | Escape special characters for Markdown.
escapeString :: String -> String
@@ -170,134 +180,131 @@ olMarker = do (start, style', delim) <- anyOrderedListMarker
-- | True if string begins with an ordered list marker
beginsWithOrderedListMarker :: String -> Bool
-beginsWithOrderedListMarker str =
- case runParser olMarker defaultParserState "para start" str of
- Left _ -> False
+beginsWithOrderedListMarker str =
+ case runParser olMarker defaultParserState "para start" (take 10 str) of
+ Left _ -> False
Right _ -> True
-wrappedMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc
-wrappedMarkdown opts inlines = do
- let chunks = splitBy LineBreak inlines
- let chunks' = if null chunks
- then []
- else (map (++ [Str " "]) $ init chunks) ++ [last chunks]
- lns <- mapM (wrapIfNeeded opts (inlineListToMarkdown opts)) chunks'
- return $ vcat lns
-
-- | Convert Pandoc block element to markdown.
blockToMarkdown :: WriterOptions -- ^ Options
-> Block -- ^ Block element
-> State WriterState Doc
blockToMarkdown _ Null = return empty
-blockToMarkdown opts (Plain inlines) =
- wrappedMarkdown opts inlines
+blockToMarkdown opts (Plain inlines) = do
+ contents <- inlineListToMarkdown opts inlines
+ return $ contents <> cr
blockToMarkdown opts (Para inlines) = do
- contents <- wrappedMarkdown opts inlines
+ contents <- inlineListToMarkdown opts inlines
-- escape if para starts with ordered list marker
- let esc = if (not (writerStrictMarkdown opts)) &&
- beginsWithOrderedListMarker (render contents)
- then char '\\'
- else empty
- return $ esc <> contents <> text "\n"
+ st <- get
+ let esc = if (not (writerStrictMarkdown opts)) &&
+ not (stPlain st) &&
+ beginsWithOrderedListMarker (render Nothing contents)
+ then text "\\"
+ else empty
+ return $ esc <> contents <> blankline
blockToMarkdown _ (RawHtml str) = do
st <- get
if stPlain st
then return empty
- else return $ text str
-blockToMarkdown _ HorizontalRule = return $ text "\n* * * * *\n"
+ else return $ text str <> text "\n"
+blockToMarkdown _ HorizontalRule =
+ return $ blankline <> text "* * * * *" <> blankline
blockToMarkdown opts (Header level inlines) = do
contents <- inlineListToMarkdown opts inlines
st <- get
-- use setext style headers if in literate haskell mode.
-- ghc interprets '#' characters in column 1 as line number specifiers.
if writerLiterateHaskell opts || stPlain st
- then let len = length $ render contents
- in return $ contents <> text "\n" <>
- case level of
- 1 -> text $ replicate len '=' ++ "\n"
- 2 -> text $ replicate len '-' ++ "\n"
- _ -> empty
- else return $ text ((replicate level '#') ++ " ") <> contents <> text "\n"
-blockToMarkdown opts (CodeBlock (_,classes,_) str) | "haskell" `elem` classes &&
- "literate" `elem` classes &&
- writerLiterateHaskell opts =
- return $ (vcat $ map (text "> " <>) $ map text (lines str)) <> text "\n"
+ then let len = offset contents
+ in return $ contents <> cr <>
+ (case level of
+ 1 -> text $ replicate len '='
+ 2 -> text $ replicate len '-'
+ _ -> empty) <> blankline
+ else return $
+ text ((replicate level '#') ++ " ") <> contents <> blankline
+blockToMarkdown opts (CodeBlock (_,classes,_) str)
+ | "haskell" `elem` classes && "literate" `elem` classes &&
+ writerLiterateHaskell opts =
+ return $ prefixed "> " (text str) <> blankline
blockToMarkdown opts (CodeBlock _ str) = return $
- (nest (writerTabStop opts) $ vcat $ map text (lines str)) <> text "\n"
+ nest (writerTabStop opts) (text str) <> blankline
blockToMarkdown opts (BlockQuote blocks) = do
st <- get
-- if we're writing literate haskell, put a space before the bird tracks
-- so they won't be interpreted as lhs...
let leader = if writerLiterateHaskell opts
- then text . (" > " ++)
+ then " > "
else if stPlain st
- then text . (" " ++)
- else text . ("> " ++)
+ then " "
+ else "> "
contents <- blockListToMarkdown opts blocks
- return $ (vcat $ map leader $ lines $ render contents) <>
- text "\n"
+ return $ (prefixed leader contents) <> blankline
blockToMarkdown opts (Table caption aligns widths headers rows) = do
caption' <- inlineListToMarkdown opts caption
let caption'' = if null caption
then empty
- else text "" $+$ (text ": " <> caption')
+ else blankline <> ": " <> caption' <> blankline
headers' <- mapM (blockListToMarkdown opts) headers
let alignHeader alignment = case alignment of
- AlignLeft -> leftAlignBlock
- AlignCenter -> centerAlignBlock
- AlignRight -> rightAlignBlock
- AlignDefault -> leftAlignBlock
+ AlignLeft -> lblock
+ AlignCenter -> cblock
+ AlignRight -> rblock
+ AlignDefault -> lblock
rawRows <- mapM (mapM (blockListToMarkdown opts)) rows
let isSimple = all (==0) widths
- let numChars = maximum . map (length . render)
+ let numChars = maximum . map offset
let widthsInChars =
if isSimple
then map ((+2) . numChars) $ transpose (headers' : rawRows)
- else map (floor . (78 *)) widths
- let makeRow = hsepBlocks . (zipWith alignHeader aligns) .
- (zipWith docToBlock widthsInChars)
+ else map (floor . (fromIntegral (writerColumns opts) *)) widths
+ let makeRow = hcat . intersperse (lblock 1 (text " ")) .
+ (zipWith3 alignHeader aligns widthsInChars)
let rows' = map makeRow rawRows
let head' = makeRow headers'
- let maxRowHeight = maximum $ map heightOfBlock (head':rows')
- let underline = hsep $
- map (\width -> text $ replicate width '-') widthsInChars
+ let maxRowHeight = maximum $ map height (head':rows')
+ let underline = cat $ intersperse (text " ") $
+ map (\width -> text (replicate width '-')) widthsInChars
let border = if maxRowHeight > 1
- then text $ replicate (sum widthsInChars + (length widthsInChars - 1)) '-'
+ then text (replicate (sum widthsInChars +
+ length widthsInChars - 1) '-')
else if all null headers
then underline
else empty
let head'' = if all null headers
then empty
- else border $+$ blockToDoc head'
- let spacer = if maxRowHeight > 1
- then text ""
- else empty
- let body = vcat $ intersperse spacer $ map blockToDoc rows'
+ else border <> cr <> head'
+ let body = if maxRowHeight > 1
+ then vsep rows'
+ else vcat rows'
let bottom = if all null headers
then underline
else border
- return $ (nest 2 $ head'' $+$ underline $+$ body $+$
- bottom $+$ caption'') <> text "\n"
+ return $ nest 2 $ head'' $$ underline $$ body $$
+ bottom $$ blankline $$ caption'' $$ blankline
blockToMarkdown opts (BulletList items) = do
contents <- mapM (bulletListItemToMarkdown opts) items
- return $ (vcat contents) <> text "\n"
+ return $ cat contents <> blankline
blockToMarkdown opts (OrderedList attribs items) = do
let markers = orderedListMarkers attribs
let markers' = map (\m -> if length m < 3
then m ++ replicate (3 - length m) ' '
- else m) markers
+ else m) markers
contents <- mapM (\(item, num) -> orderedListItemToMarkdown opts item num) $
- zip markers' items
- return $ (vcat contents) <> text "\n"
+ zip markers' items
+ return $ cat contents <> blankline
blockToMarkdown opts (DefinitionList items) = do
contents <- mapM (definitionListItemToMarkdown opts) items
- return $ (vcat contents) <> text "\n"
+ return $ cat contents <> blankline
-- | Convert bullet list item (list of blocks) to markdown.
bulletListItemToMarkdown :: WriterOptions -> [Block] -> State WriterState Doc
bulletListItemToMarkdown opts items = do
contents <- blockListToMarkdown opts items
- return $ hang' (text "- ") (writerTabStop opts) contents
+ let sps = replicate (writerTabStop opts - 2) ' '
+ let start = text ('-' : ' ' : sps)
+ return $ hang (writerTabStop opts) start $ contents <> cr
-- | Convert ordered list item (a list of blocks) to markdown.
orderedListItemToMarkdown :: WriterOptions -- ^ options
@@ -306,8 +313,11 @@ orderedListItemToMarkdown :: WriterOptions -- ^ options
-> State WriterState Doc
orderedListItemToMarkdown opts marker items = do
contents <- blockListToMarkdown opts items
- return $ hsep [nest (min (3 - length marker) 0) (text marker),
- nest (writerTabStop opts) contents]
+ let sps = case length marker - writerTabStop opts of
+ n | n > 0 -> text $ replicate n ' '
+ _ -> text " "
+ let start = text marker <> sps
+ return $ hang (writerTabStop opts) start $ contents <> cr
-- | Convert definition list item (label, list of blocks) to markdown.
definitionListItemToMarkdown :: WriterOptions
@@ -317,17 +327,20 @@ definitionListItemToMarkdown opts (label, defs) = do
labelText <- inlineListToMarkdown opts label
let tabStop = writerTabStop opts
st <- get
- let leader = if stPlain st then empty else text " ~"
- contents <- liftM vcat $
- mapM (liftM ((leader $$) . nest tabStop . vcat) . mapM (blockToMarkdown opts)) defs
- return $ labelText $+$ contents
+ let leader = if stPlain st then " " else " ~"
+ let sps = case writerTabStop opts - 3 of
+ n | n > 0 -> text $ replicate n ' '
+ _ -> text " "
+ defs' <- mapM (mapM (blockToMarkdown opts)) defs
+ let contents = vcat $ map (\d -> hang tabStop (leader <> sps) $ vcat d <> cr) defs'
+ return $ labelText <> cr <> contents <> cr
-- | Convert list of Pandoc block elements to markdown.
blockListToMarkdown :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
-> State WriterState Doc
blockListToMarkdown opts blocks =
- mapM (blockToMarkdown opts) blocks >>= return . vcat
+ mapM (blockToMarkdown opts) blocks >>= return . cat
-- | Get reference for target; if none exists, create unique one and return.
-- Prefer label if possible; otherwise, generate a unique key.
@@ -350,38 +363,43 @@ getReference label (src, tit) = do
-- | Convert list of Pandoc inline elements to markdown.
inlineListToMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc
inlineListToMarkdown opts lst =
- mapM (inlineToMarkdown opts) lst >>= return . hcat
+ mapM (inlineToMarkdown opts) lst >>= return . cat
+
+escapeSpaces :: Inline -> Inline
+escapeSpaces (Str s) = Str $ substitute " " "\\ " s
+escapeSpaces Space = Str "\\ "
+escapeSpaces x = x
-- | Convert Pandoc inline element to markdown.
inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
inlineToMarkdown opts (Emph lst) = do
contents <- inlineListToMarkdown opts lst
- return $ char '*' <> contents <> char '*'
+ return $ "*" <> contents <> "*"
inlineToMarkdown opts (Strong lst) = do
contents <- inlineListToMarkdown opts lst
- return $ text "**" <> contents <> text "**"
+ return $ "**" <> contents <> "**"
inlineToMarkdown opts (Strikeout lst) = do
contents <- inlineListToMarkdown opts lst
- return $ text "~~" <> contents <> text "~~"
+ return $ "~~" <> contents <> "~~"
inlineToMarkdown opts (Superscript lst) = do
- contents <- inlineListToMarkdown opts lst
- let contents' = text $ substitute " " "\\ " $ render contents
- return $ char '^' <> contents' <> char '^'
+ let lst' = processWith escapeSpaces lst
+ contents <- inlineListToMarkdown opts lst'
+ return $ "^" <> contents <> "^"
inlineToMarkdown opts (Subscript lst) = do
- contents <- inlineListToMarkdown opts lst
- let contents' = text $ substitute " " "\\ " $ render contents
- return $ char '~' <> contents' <> char '~'
+ let lst' = processWith escapeSpaces lst
+ contents <- inlineListToMarkdown opts lst'
+ return $ "~" <> contents <> "~"
inlineToMarkdown opts (SmallCaps lst) = inlineListToMarkdown opts lst
inlineToMarkdown opts (Quoted SingleQuote lst) = do
contents <- inlineListToMarkdown opts lst
- return $ char '‘' <> contents <> char '’'
+ return $ "‘" <> contents <> "’"
inlineToMarkdown opts (Quoted DoubleQuote lst) = do
contents <- inlineListToMarkdown opts lst
- return $ char '“' <> contents <> char '”'
-inlineToMarkdown _ EmDash = return $ char '\8212'
-inlineToMarkdown _ EnDash = return $ char '\8211'
-inlineToMarkdown _ Apostrophe = return $ char '\8217'
-inlineToMarkdown _ Ellipses = return $ char '\8230'
+ return $ "“" <> contents <> "”"
+inlineToMarkdown _ EmDash = return "\8212"
+inlineToMarkdown _ EnDash = return "\8211"
+inlineToMarkdown _ Apostrophe = return "\8217"
+inlineToMarkdown _ Ellipses = return "\8230"
inlineToMarkdown _ (Code str) =
let tickGroups = filter (\s -> '`' `elem` s) $ group str
longest = if null tickGroups
@@ -395,25 +413,27 @@ inlineToMarkdown _ (Str str) = do
if stPlain st
then return $ text str
else return $ text $ escapeString str
-inlineToMarkdown _ (Math InlineMath str) = return $ char '$' <> text str <> char '$'
-inlineToMarkdown _ (Math DisplayMath str) = return $ text "$$" <> text str <> text "$$"
+inlineToMarkdown _ (Math InlineMath str) =
+ return $ "$" <> text str <> "$"
+inlineToMarkdown _ (Math DisplayMath str) =
+ return $ "$$" <> text str <> "$$"
inlineToMarkdown _ (TeX str) = return $ text str
inlineToMarkdown _ (HtmlInline str) = return $ text str
-inlineToMarkdown _ (LineBreak) = return $ text " \n"
-inlineToMarkdown _ Space = return $ char ' '
+inlineToMarkdown _ (LineBreak) = return $ " " <> cr
+inlineToMarkdown _ Space = return space
inlineToMarkdown opts (Cite (c:cs) lst)
| writerCiteMethod opts == Citeproc = inlineListToMarkdown opts lst
| citationMode c == AuthorInText = do
suffs <- inlineListToMarkdown opts $ citationSuffix c
rest <- mapM convertOne cs
let inbr = suffs <+> joincits rest
- br = if isEmpty inbr then empty else brackets inbr
+ br = if isEmpty inbr then empty else char '[' <> inbr <> char ']'
return $ text ("@" ++ citationId c) <+> br
| otherwise = do
cits <- mapM convertOne (c:cs)
return $ text "[" <> joincits cits <> text "]"
where
- joincits = hcat . punctuate (text "; ") . filter (not . isEmpty)
+ joincits = hcat . intersperse (text "; ") . filter (not . isEmpty)
convertOne Citation { citationId = k
, citationPrefix = pinlines
, citationSuffix = sinlines
@@ -431,7 +451,9 @@ inlineToMarkdown opts (Cite (c:cs) lst)
inlineToMarkdown _ (Cite _ _) = return $ text ""
inlineToMarkdown opts (Link txt (src', tit)) = do
linktext <- inlineListToMarkdown opts txt
- let linktitle = if null tit then empty else text $ " \"" ++ tit ++ "\""
+ let linktitle = if null tit
+ then empty
+ else text $ " \"" ++ tit ++ "\""
let src = unescapeURI src'
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
let useRefLinks = writerReferenceLinks opts
@@ -439,24 +461,24 @@ inlineToMarkdown opts (Link txt (src', tit)) = do
ref <- if useRefLinks then getReference txt (src, tit) else return []
reftext <- inlineListToMarkdown opts ref
return $ if useAuto
- then char '<' <> text srcSuffix <> char '>'
+ then "<" <> text srcSuffix <> ">"
else if useRefLinks
- then let first = char '[' <> linktext <> char ']'
+ then let first = "[" <> linktext <> "]"
second = if txt == ref
- then text "[]"
- else char '[' <> reftext <> char ']'
+ then "[]"
+ else "[" <> reftext <> "]"
in first <> second
- else char '[' <> linktext <> char ']' <>
- char '(' <> text src <> linktitle <> char ')'
+ else "[" <> linktext <> "](" <>
+ text src <> linktitle <> ")"
inlineToMarkdown opts (Image alternate (source, tit)) = do
let txt = if (null alternate) || (alternate == [Str ""]) ||
(alternate == [Str source]) -- to prevent autolinks
then [Str "image"]
else alternate
linkPart <- inlineToMarkdown opts (Link txt (unescapeURI source, tit))
- return $ char '!' <> linkPart
+ return $ "!" <> linkPart
inlineToMarkdown _ (Note contents) = do
modify (\st -> st{ stNotes = contents : stNotes st })
st <- get
let ref = show $ (length $ stNotes st)
- return $ text "[^" <> text ref <> char ']'
+ return $ "[^" <> text ref <> "]"
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 862628f9d..59f7e14f5 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 Puneeth Chaganti <punchagan@gmail.com>
@@ -32,10 +33,9 @@ Org-Mode: <http://orgmode.org>
module Text.Pandoc.Writers.Org ( writeOrg) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
-import Text.Pandoc.Blocks
+import Text.Pandoc.Pretty
import Text.Pandoc.Templates (renderTemplate)
import Data.List ( intersect, intersperse, transpose )
-import Text.PrettyPrint.HughesPJ hiding ( Str )
import Control.Monad.State
import Control.Applicative ( (<$>) )
@@ -66,13 +66,16 @@ pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do
notes <- liftM (reverse . stNotes) get >>= notesToOrg
-- note that the notes may contain refs, so we do them first
hasMath <- liftM stHasMath get
- let main = render $ foldl ($+$) empty $ [body, notes]
+ let colwidth = if writerWrapText opts
+ then Just $ writerColumns opts
+ else Nothing
+ let main = render colwidth $ foldl ($+$) empty $ [body, notes]
let context = writerVariables opts ++
[ ("body", main)
- , ("title", render title)
- , ("date", render date) ] ++
+ , ("title", render Nothing title)
+ , ("date", render Nothing date) ] ++
[ ("math", "yes") | hasMath ] ++
- [ ("author", render a) | a <- authors ]
+ [ ("author", render Nothing a) | a <- authors ]
if writerStandalone opts
then return $ renderTemplate context $ writerTemplate opts
else return main
@@ -81,22 +84,14 @@ pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do
notesToOrg :: [[Block]] -> State WriterState Doc
notesToOrg notes =
mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>=
- return . vcat
+ return . vsep
-- | Return Org representation of a note.
noteToOrg :: Int -> [Block] -> State WriterState Doc
noteToOrg num note = do
contents <- blockListToOrg note
- let marker = text "[" <> text (show num) <> text "] "
- return $ marker <> contents
-
--- | Take list of inline elements and return wrapped doc.
-wrappedOrg :: WriterOptions -> [Inline] -> State WriterState Doc
-wrappedOrg opts inlines = do
- lineBreakDoc <- inlineToOrg LineBreak
- chunks <- mapM (wrapIfNeeded opts inlineListToOrg)
- (splitBy LineBreak inlines)
- return $ vcat $ intersperse lineBreakDoc chunks
+ let marker = "[" ++ show num ++ "] "
+ return $ hang (length marker) (text marker) contents
-- | Escape special characters for Org.
escapeString :: String -> String
@@ -106,32 +101,28 @@ titleToOrg :: [Inline] -> State WriterState Doc
titleToOrg [] = return empty
titleToOrg lst = do
contents <- inlineListToOrg lst
- let titleName = text "#+TITLE: "
- return $ titleName <> contents
+ return $ "#+TITLE: " <> contents
-- | Convert Pandoc block element to Org.
blockToOrg :: Block -- ^ Block element
-> State WriterState Doc
blockToOrg Null = return empty
-blockToOrg (Plain inlines) = do
- opts <- get >>= (return . stOptions)
- wrappedOrg opts inlines
+blockToOrg (Plain inlines) = inlineListToOrg inlines
blockToOrg (Para [Image txt (src,tit)]) = do
capt <- inlineListToOrg txt
img <- inlineToOrg (Image txt (src,tit))
- return $ text "#+CAPTION: " <> capt <> text "\n" $$ img
+ return $ "#+CAPTION: " <> capt <> blankline <> img
blockToOrg (Para inlines) = do
- opts <- get >>= (return . stOptions)
- contents <- wrappedOrg opts inlines
- return $ contents <> text "\n"
+ contents <- inlineListToOrg inlines
+ return $ contents <> blankline
blockToOrg (RawHtml str) =
- return $ (text "\n#+BEGIN_HTML\n") $$ (nest 2 $ vcat $ map text (lines str))
- $$ (text "\n#+END_HTML\n")
-blockToOrg HorizontalRule = return $ text "--------------\n"
+ return $ blankline $$ "#+BEGIN_HTML" $$
+ nest 2 (text str) $$ "#+END_HTML" $$ blankline
+blockToOrg HorizontalRule = return $ blankline $$ "--------------" $$ blankline
blockToOrg (Header level inlines) = do
contents <- inlineListToOrg inlines
let headerStr = text $ if level > 999 then " " else replicate level '*'
- return $ headerStr <> text " " <> contents <> text "\n"
+ return $ headerStr <> " " <> contents <> blankline
blockToOrg (CodeBlock (_,classes,_) str) = do
opts <- stOptions <$> get
let tabstop = writerTabStop opts
@@ -143,31 +134,30 @@ blockToOrg (CodeBlock (_,classes,_) str) = do
let (beg, end) = if null at
then ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE")
else ("#+BEGIN_SRC" ++ head at, "#+END_SRC")
- return $ text beg $+$ (nest tabstop $ vcat $ map text (lines str))
- $+$ text end
+ return $ text beg $$ nest tabstop (text str) $$ text end $$ blankline
blockToOrg (BlockQuote blocks) = do
contents <- blockListToOrg blocks
- return $ (text "\n#+BEGIN_QUOTE\n") $$ (nest 2 contents)
- $$ (text "\n#+END_QUOTE\n")
+ return $ blankline $$ "#+BEGIN_QUOTE" $$
+ nest 2 contents $$ "#+END_QUOTE" $$ blankline
blockToOrg (Table caption' _ _ headers rows) = do
caption'' <- inlineListToOrg caption'
let caption = if null caption'
then empty
- else (text "#+CAPTION: " <> caption'')
+ else ("#+CAPTION: " <> caption'')
headers' <- mapM blockListToOrg headers
rawRows <- mapM (mapM blockListToOrg) rows
- let numChars = maximum . map (length . render)
+ let numChars = maximum . map offset
-- FIXME: width is not being used.
let widthsInChars =
map ((+2) . numChars) $ transpose (headers' : rawRows)
-- FIXME: Org doesn't allow blocks with height more than 1.
- let hpipeBlocks blocks = hcatBlocks [beg, middle, end]
- where height = maximum (map heightOfBlock blocks)
- sep' = TextBlock 3 height (replicate height " | ")
- beg = TextBlock 2 height (replicate height "| ")
- end = TextBlock 2 height (replicate height " |")
- middle = hcatBlocks $ intersperse sep' blocks
- let makeRow = hpipeBlocks . zipWith docToBlock widthsInChars
+ let hpipeBlocks blocks = hcat [beg, middle, end]
+ where h = maximum (map height blocks)
+ sep' = lblock 3 $ vcat (map text $ replicate h " | ")
+ beg = lblock 2 $ vcat (map text $ replicate h "| ")
+ end = lblock 2 $ vcat (map text $ replicate h " |")
+ middle = hcat $ intersperse sep' blocks
+ let makeRow = hpipeBlocks . zipWith lblock widthsInChars
let head' = makeRow headers'
rows' <- mapM (\row -> do cols <- mapM blockListToOrg row
return $ makeRow cols) rows
@@ -175,34 +165,37 @@ blockToOrg (Table caption' _ _ headers rows) = do
(hcat $ intersperse (char ch <> char '+' <> char ch) $
map (\l -> text $ replicate l ch) widthsInChars) <>
char ch <> char '|'
- let body = vcat $ map blockToDoc rows'
+ let body = vcat rows'
let head'' = if all null headers
then empty
- else blockToDoc head' $+$ border '-'
- return $ head'' $+$ body $$ caption $$ text ""
+ else head' $$ border '-'
+ return $ head'' $$ body $$ caption $$ blankline
blockToOrg (BulletList items) = do
contents <- mapM bulletListItemToOrg items
-- ensure that sublists have preceding blank line
- return $ text "" $+$ vcat contents <> text "\n"
-blockToOrg (OrderedList (start, style', delim) items) = do
+ return $ blankline $+$ vcat contents $$ blankline
+blockToOrg (OrderedList (start, _, delim) items) = do
+ let delim' = case delim of
+ TwoParens -> OneParen
+ x -> x
let markers = take (length items) $ orderedListMarkers
- (start, style', delim)
+ (start, Decimal, delim')
let maxMarkerLength = maximum $ map length markers
let markers' = map (\m -> let s = maxMarkerLength - length m
in m ++ replicate s ' ') markers
contents <- mapM (\(item, num) -> orderedListItemToOrg item num) $
- zip markers' items
+ zip markers' items
-- ensure that sublists have preceding blank line
- return $ text "" $+$ vcat contents <> text "\n"
+ return $ blankline $$ vcat contents $$ blankline
blockToOrg (DefinitionList items) = do
contents <- mapM definitionListItemToOrg items
- return $ (vcat contents) <> text "\n"
+ return $ vcat contents $$ blankline
-- | Convert bullet list item (list of blocks) to Org.
bulletListItemToOrg :: [Block] -> State WriterState Doc
bulletListItemToOrg items = do
contents <- blockListToOrg items
- return $ (text "- ") <> contents
+ return $ hang 3 "- " (contents <> cr)
-- | Convert ordered list item (a list of blocks) to Org.
orderedListItemToOrg :: String -- ^ marker for list item
@@ -210,14 +203,14 @@ orderedListItemToOrg :: String -- ^ marker for list item
-> State WriterState Doc
orderedListItemToOrg marker items = do
contents <- blockListToOrg items
- return $ (text marker <> char ' ') <> contents
+ return $ hang (length marker + 1) (text marker <> space) (contents <> cr)
-- | Convert defintion list item (label, list of blocks) to Org.
definitionListItemToOrg :: ([Inline], [[Block]]) -> State WriterState Doc
definitionListItemToOrg (label, defs) = do
label' <- inlineListToOrg label
contents <- liftM vcat $ mapM blockListToOrg defs
- return $ (text "- ") <> label' <> (text " :: ") <> contents
+ return $ hang 3 "- " $ label' <> " :: " <> (contents <> cr)
-- | Convert list of Pandoc block elements to Org.
blockListToOrg :: [Block] -- ^ List of block elements
@@ -232,60 +225,57 @@ inlineListToOrg lst = mapM inlineToOrg lst >>= return . hcat
inlineToOrg :: Inline -> State WriterState Doc
inlineToOrg (Emph lst) = do
contents <- inlineListToOrg lst
- return $ char '/' <> contents <> char '/'
+ return $ "/" <> contents <> "/"
inlineToOrg (Strong lst) = do
contents <- inlineListToOrg lst
- return $ text "*" <> contents <> text "*"
+ return $ "*" <> contents <> "*"
inlineToOrg (Strikeout lst) = do
contents <- inlineListToOrg lst
- return $ text "+" <> contents <> char '+'
+ return $ "+" <> contents <> "+"
inlineToOrg (Superscript lst) = do
contents <- inlineListToOrg lst
- return $ text "^{" <> contents <> text "}"
+ return $ "^{" <> contents <> "}"
inlineToOrg (Subscript lst) = do
contents <- inlineListToOrg lst
- return $ text "_{" <> contents <> text "}"
+ return $ "_{" <> contents <> "}"
inlineToOrg (SmallCaps lst) = inlineListToOrg lst
inlineToOrg (Quoted SingleQuote lst) = do
contents <- inlineListToOrg lst
- return $ char '\'' <> contents <> char '\''
+ return $ "'" <> contents <> "'"
inlineToOrg (Quoted DoubleQuote lst) = do
contents <- inlineListToOrg lst
- return $ char '\"' <> contents <> char '\"'
-inlineToOrg (Cite _ lst) =
- inlineListToOrg lst
-inlineToOrg EmDash = return $ text "---"
-inlineToOrg EnDash = return $ text "--"
-inlineToOrg Apostrophe = return $ char '\''
-inlineToOrg Ellipses = return $ text "..."
-inlineToOrg (Code str) = return $ text $ "=" ++ str ++ "="
+ return $ "\"" <> contents <> "\""
+inlineToOrg (Cite _ lst) = inlineListToOrg lst
+inlineToOrg EmDash = return "---"
+inlineToOrg EnDash = return "--"
+inlineToOrg Apostrophe = return "'"
+inlineToOrg Ellipses = return "..."
+inlineToOrg (Code str) = return $ "=" <> text str <> "="
inlineToOrg (Str str) = return $ text $ escapeString str
inlineToOrg (Math t str) = do
modify $ \st -> st{ stHasMath = True }
return $ if t == InlineMath
- then text $ "$" ++ str ++ "$"
- else text $ "$$" ++ str ++ "$$"
+ then "$" <> text str <> "$"
+ else "$$" <> text str <> "$$"
inlineToOrg (TeX str) = return $ text str
inlineToOrg (HtmlInline _) = return empty
-inlineToOrg (LineBreak) = do
- return $ empty -- there's no line break in Org
-inlineToOrg Space = return $ char ' '
+inlineToOrg (LineBreak) = return cr -- there's no line break in Org
+inlineToOrg Space = return space
inlineToOrg (Link txt (src, _)) = do
case txt of
[Code x] | x == src -> -- autolink
do modify $ \s -> s{ stLinks = True }
- return $ text $ "[[" ++ x ++ "]]"
+ return $ "[[" <> text x <> "]]"
_ -> do contents <- inlineListToOrg txt
modify $ \s -> s{ stLinks = True }
- return $ text ("[[" ++ src ++ "][") <> contents <>
- (text "]]")
+ return $ "[[" <> text src <> "][" <> contents <> "]]"
inlineToOrg (Image _ (source', _)) = do
let source = unescapeURI source'
modify $ \s -> s{ stImages = True }
- return $ text $ "[[" ++ source ++ "]]"
+ return $ "[[" <> text source <> "]]"
inlineToOrg (Note contents) = do
-- add to notes in state
notes <- get >>= (return . stNotes)
modify $ \st -> st { stNotes = contents:notes }
let ref = show $ (length notes) + 1
- return $ text " [" <> text ref <> text "]"
+ return $ " [" <> text ref <> "]"
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index e79f97b33..908549041 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
@@ -32,10 +33,9 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html>
module Text.Pandoc.Writers.RST ( writeRST) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
-import Text.Pandoc.Blocks
import Text.Pandoc.Templates (renderTemplate)
-import Data.List ( isPrefixOf, isSuffixOf, intersperse, transpose )
-import Text.PrettyPrint.HughesPJ hiding ( Str )
+import Data.List ( isPrefixOf, intersperse, transpose )
+import Text.Pandoc.Pretty
import Control.Monad.State
import Control.Applicative ( (<$>) )
@@ -70,13 +70,16 @@ pandocToRST (Pandoc (Meta tit auth dat) blocks) = do
refs <- liftM (reverse . stLinks) get >>= refsToRST
pics <- liftM (reverse . stImages) get >>= pictRefsToRST
hasMath <- liftM stHasMath get
- let main = render $ foldl ($+$) empty $ [body, notes, refs, pics]
+ let colwidth = if writerWrapText opts
+ then Just $ writerColumns opts
+ else Nothing
+ let main = render colwidth $ foldl ($+$) empty $ [body, notes, refs, pics]
let context = writerVariables opts ++
[ ("body", main)
- , ("title", render title)
- , ("date", render date) ] ++
+ , ("title", render Nothing title)
+ , ("date", render colwidth date) ] ++
[ ("math", "yes") | hasMath ] ++
- [ ("author", render a) | a <- authors ]
+ [ ("author", render colwidth a) | a <- authors ]
if writerStandalone opts
then return $ renderTemplate context $ writerTemplate opts
else return main
@@ -84,49 +87,40 @@ pandocToRST (Pandoc (Meta tit auth dat) blocks) = do
-- | Return RST representation of reference key table.
refsToRST :: Refs -> State WriterState Doc
refsToRST refs = mapM keyToRST refs >>= return . vcat
-
+
-- | Return RST representation of a reference key.
keyToRST :: ([Inline], (String, String))
-> State WriterState Doc
keyToRST (label, (src, _)) = do
label' <- inlineListToRST label
- let label'' = if ':' `elem` (render label')
+ let label'' = if ':' `elem` (render Nothing label')
then char '`' <> label' <> char '`'
else label'
- return $ text ".. _" <> label'' <> text ": " <> text src
+ return $ ".. _" <> label'' <> ": " <> text src
-- | Return RST representation of notes.
notesToRST :: [[Block]] -> State WriterState Doc
notesToRST notes =
- mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>=
- return . vcat
+ mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>=
+ return . vsep
-- | Return RST representation of a note.
noteToRST :: Int -> [Block] -> State WriterState Doc
noteToRST num note = do
contents <- blockListToRST note
- let marker = text ".. [" <> text (show num) <> text "]"
+ let marker = ".. [" <> text (show num) <> "]"
return $ marker $$ nest 3 contents
-- | Return RST representation of picture reference table.
pictRefsToRST :: Refs -> State WriterState Doc
pictRefsToRST refs = mapM pictToRST refs >>= return . vcat
-
+
-- | Return RST representation of a picture substitution reference.
pictToRST :: ([Inline], (String, String))
-> State WriterState Doc
pictToRST (label, (src, _)) = do
label' <- inlineListToRST label
- return $ text ".. " <> char '|' <> label' <> char '|' <> text " image:: " <>
- text src
-
--- | Take list of inline elements and return wrapped doc.
-wrappedRST :: WriterOptions -> [Inline] -> State WriterState Doc
-wrappedRST opts inlines = do
- lineBreakDoc <- inlineToRST LineBreak
- chunks <- mapM (wrapIfNeeded opts inlineListToRST)
- (splitBy LineBreak inlines)
- return $ vcat $ intersperse lineBreakDoc chunks
+ return $ ".. |" <> label' <> "| image:: " <> text src
-- | Escape special characters for RST.
escapeString :: String -> String
@@ -136,69 +130,66 @@ titleToRST :: [Inline] -> State WriterState Doc
titleToRST [] = return empty
titleToRST lst = do
contents <- inlineListToRST lst
- let titleLength = length $ render contents
+ let titleLength = length $ (render Nothing contents :: String)
let border = text (replicate titleLength '=')
- return $ border $+$ contents $+$ border
+ return $ border $$ contents $$ border
-- | Convert Pandoc block element to RST.
blockToRST :: Block -- ^ Block element
-> State WriterState Doc
blockToRST Null = return empty
-blockToRST (Plain inlines) = do
- opts <- get >>= (return . stOptions)
- wrappedRST opts inlines
+blockToRST (Plain inlines) = inlineListToRST inlines
blockToRST (Para [Image txt (src,tit)]) = do
capt <- inlineListToRST txt
- let fig = text "figure:: " <> text src
- let align = text ":align: center"
- let alt = text ":alt: " <> if null tit then capt else text tit
- return $ (text ".. " <> (fig $$ align $$ alt $$ text "" $$ capt)) $$ text ""
+ let fig = "figure:: " <> text src
+ let align = ":align: center"
+ let alt = ":alt: " <> if null tit then capt else text tit
+ return $ hang 3 ".. " $ fig $$ align $$ alt $+$ capt $$ blankline
blockToRST (Para inlines) = do
- opts <- get >>= (return . stOptions)
- contents <- wrappedRST opts inlines
- return $ contents <> text "\n"
-blockToRST (RawHtml str) =
- let str' = if "\n" `isSuffixOf` str then str ++ "\n" else str ++ "\n\n" in
- return $ (text "\n.. raw:: html\n") $$ (nest 3 $ vcat $ map text (lines str'))
-blockToRST HorizontalRule = return $ text "--------------\n"
+ contents <- inlineListToRST inlines
+ return $ contents <> blankline
+blockToRST (RawHtml str) =
+ return $ blankline <> ".. raw:: html" $+$
+ (nest 3 $ text str) <> blankline
+blockToRST HorizontalRule =
+ return $ blankline $$ "--------------" $$ blankline
blockToRST (Header level inlines) = do
contents <- inlineListToRST inlines
- let headerLength = length $ render contents
let headerChar = if level > 5 then ' ' else "=-~^'" !! (level - 1)
- let border = text $ replicate headerLength headerChar
- return $ contents $+$ border <> text "\n"
+ let border = text $ replicate (offset contents) headerChar
+ return $ contents $$ border $$ blankline
blockToRST (CodeBlock (_,classes,_) str) = do
opts <- stOptions <$> get
let tabstop = writerTabStop opts
if "haskell" `elem` classes && "literate" `elem` classes &&
writerLiterateHaskell opts
- then return $ (vcat $ map (text "> " <>) $ map text (lines str)) <> text "\n"
- else return $ (text "::\n") $+$
- (nest tabstop $ vcat $ map text (lines str)) <> text "\n"
+ then return $ prefixed "> " $ text str $$ blankline
+ else return $ "::" $+$ nest tabstop (text str) $$ blankline
blockToRST (BlockQuote blocks) = do
tabstop <- get >>= (return . writerTabStop . stOptions)
contents <- blockListToRST blocks
- return $ (nest tabstop contents) <> text "\n"
+ return $ nest tabstop contents <> blankline
blockToRST (Table caption _ widths headers rows) = do
caption' <- inlineListToRST caption
let caption'' = if null caption
then empty
- else text "" $+$ (text "Table: " <> caption')
+ else blankline <> text "Table: " <> caption'
headers' <- mapM blockListToRST headers
rawRows <- mapM (mapM blockListToRST) rows
let isSimple = all (==0) widths && all (all (\bs -> length bs == 1)) rows
- let numChars = maximum . map (length . render)
+ let numChars = maximum . map offset
+ opts <- get >>= return . stOptions
let widthsInChars =
if isSimple
then map ((+2) . numChars) $ transpose (headers' : rawRows)
- else map (floor . (78 *)) widths
- let hpipeBlocks blocks = hcatBlocks [beg, middle, end]
- where height = maximum (map heightOfBlock blocks)
- sep' = TextBlock 3 height (replicate height " | ")
- beg = TextBlock 2 height (replicate height "| ")
- end = TextBlock 2 height (replicate height " |")
- middle = hcatBlocks $ intersperse sep' blocks
- let makeRow = hpipeBlocks . zipWith docToBlock widthsInChars
+ else map (floor . (fromIntegral (writerColumns opts) *)) widths
+ let hpipeBlocks blocks = hcat [beg, middle, end]
+ where h = maximum (map height blocks)
+ sep' = lblock 3 $ vcat (map text $ replicate h " | ")
+ beg = lblock 2 $ vcat (map text $ replicate h "| ")
+ end = lblock 2 $ vcat (map text $ replicate h " |")
+ middle = hcat $ intersperse sep' blocks
+ let makeRow = hpipeBlocks . zipWith lblock widthsInChars
let head' = makeRow headers'
rows' <- mapM (\row -> do cols <- mapM blockListToRST row
return $ makeRow cols) rows
@@ -206,15 +197,15 @@ blockToRST (Table caption _ widths headers rows) = do
(hcat $ intersperse (char ch <> char '+' <> char ch) $
map (\l -> text $ replicate l ch) widthsInChars) <>
char ch <> char '+'
- let body = vcat $ intersperse (border '-') $ map blockToDoc rows'
+ let body = vcat $ intersperse (border '-') rows'
let head'' = if all null headers
then empty
- else blockToDoc head' $+$ border '='
- return $ border '-' $+$ head'' $+$ body $+$ border '-' $$ caption'' $$ text ""
+ else head' $$ border '='
+ return $ border '-' $$ head'' $$ body $$ border '-' $$ caption'' $$ blankline
blockToRST (BulletList items) = do
contents <- mapM bulletListItemToRST items
-- ensure that sublists have preceding blank line
- return $ text "" $+$ vcat contents <> text "\n"
+ return $ blankline $$ vcat contents $$ blankline
blockToRST (OrderedList (start, style', delim) items) = do
let markers = if start == 1 && style' == DefaultStyle && delim == DefaultDelim
then take (length items) $ repeat "#."
@@ -224,18 +215,19 @@ blockToRST (OrderedList (start, style', delim) items) = do
let markers' = map (\m -> let s = maxMarkerLength - length m
in m ++ replicate s ' ') markers
contents <- mapM (\(item, num) -> orderedListItemToRST item num) $
- zip markers' items
+ zip markers' items
-- ensure that sublists have preceding blank line
- return $ text "" $+$ vcat contents <> text "\n"
+ return $ blankline $$ vcat contents $$ blankline
blockToRST (DefinitionList items) = do
contents <- mapM definitionListItemToRST items
- return $ (vcat contents) <> text "\n"
+ -- ensure that sublists have preceding blank line
+ return $ blankline $$ vcat contents $$ blankline
-- | Convert bullet list item (list of blocks) to RST.
bulletListItemToRST :: [Block] -> State WriterState Doc
bulletListItemToRST items = do
contents <- blockListToRST items
- return $ (text "- ") <> contents
+ return $ hang 3 "- " $ contents <> cr
-- | Convert ordered list item (a list of blocks) to RST.
orderedListItemToRST :: String -- ^ marker for list item
@@ -243,7 +235,8 @@ orderedListItemToRST :: String -- ^ marker for list item
-> State WriterState Doc
orderedListItemToRST marker items = do
contents <- blockListToRST items
- return $ (text marker <> char ' ') <> contents
+ let marker' = marker ++ " "
+ return $ hang (length marker') (text marker') $ contents <> cr
-- | Convert defintion list item (label, list of blocks) to RST.
definitionListItemToRST :: ([Inline], [[Block]]) -> State WriterState Doc
@@ -251,7 +244,7 @@ definitionListItemToRST (label, defs) = do
label' <- inlineListToRST label
contents <- liftM vcat $ mapM blockListToRST defs
tabstop <- get >>= (return . writerTabStop . stOptions)
- return $ label' $+$ nest tabstop contents
+ return $ label' $$ nest tabstop (contents <> cr)
-- | Convert list of Pandoc block elements to RST.
blockListToRST :: [Block] -- ^ List of block elements
@@ -266,65 +259,64 @@ inlineListToRST lst = mapM inlineToRST lst >>= return . hcat
inlineToRST :: Inline -> State WriterState Doc
inlineToRST (Emph lst) = do
contents <- inlineListToRST lst
- return $ char '*' <> contents <> char '*'
+ return $ "*" <> contents <> "*"
inlineToRST (Strong lst) = do
contents <- inlineListToRST lst
- return $ text "**" <> contents <> text "**"
+ return $ "**" <> contents <> "**"
inlineToRST (Strikeout lst) = do
contents <- inlineListToRST lst
- return $ text "[STRIKEOUT:" <> contents <> char ']'
+ return $ "[STRIKEOUT:" <> contents <> "]"
inlineToRST (Superscript lst) = do
contents <- inlineListToRST lst
- return $ text "\\ :sup:`" <> contents <> text "`\\ "
+ return $ "\\ :sup:`" <> contents <> "`\\ "
inlineToRST (Subscript lst) = do
contents <- inlineListToRST lst
- return $ text "\\ :sub:`" <> contents <> text "`\\ "
+ return $ "\\ :sub:`" <> contents <> "`\\ "
inlineToRST (SmallCaps lst) = inlineListToRST lst
inlineToRST (Quoted SingleQuote lst) = do
contents <- inlineListToRST lst
- return $ char '‘' <> contents <> char '’'
+ return $ "‘" <> contents <> "’"
inlineToRST (Quoted DoubleQuote lst) = do
contents <- inlineListToRST lst
- return $ char '“' <> contents <> char '”'
+ return $ "“" <> contents <> "”"
inlineToRST (Cite _ lst) =
inlineListToRST lst
inlineToRST EmDash = return $ char '\8212'
inlineToRST EnDash = return $ char '\8211'
inlineToRST Apostrophe = return $ char '\8217'
inlineToRST Ellipses = return $ char '\8230'
-inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``"
+inlineToRST (Code str) = return $ "``" <> text str <> "``"
inlineToRST (Str str) = return $ text $ escapeString str
inlineToRST (Math t str) = do
modify $ \st -> st{ stHasMath = True }
return $ if t == InlineMath
- then text $ ":math:`$" ++ str ++ "$`"
- else text $ ":math:`$$" ++ str ++ "$$`"
+ then ":math:`$" <> text str <> "$`"
+ else ":math:`$$" <> text str <> "$$`"
inlineToRST (TeX _) = return empty
inlineToRST (HtmlInline _) = return empty
-inlineToRST (LineBreak) = do
- return $ empty -- there's no line break in RST
-inlineToRST Space = return $ char ' '
+inlineToRST (LineBreak) = return cr -- there's no line break in RST
+inlineToRST Space = return space
inlineToRST (Link [Code str] (src, _)) | src == str ||
src == "mailto:" ++ str = do
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
return $ text $ unescapeURI srcSuffix
inlineToRST (Link txt (src', tit)) = do
let src = unescapeURI src'
- useReferenceLinks <- get >>= (return . writerReferenceLinks . stOptions)
+ useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions
linktext <- inlineListToRST $ normalizeSpaces txt
if useReferenceLinks
- then do refs <- get >>= (return . stLinks)
+ then do refs <- get >>= return . stLinks
let refs' = if (txt, (src, tit)) `elem` refs
then refs
else (txt, (src, tit)):refs
modify $ \st -> st { stLinks = refs' }
- return $ char '`' <> linktext <> text "`_"
- else return $ char '`' <> linktext <> text " <" <> text src <> text ">`_"
+ return $ "`" <> linktext <> "`_"
+ else return $ "`" <> linktext <> " <" <> text src <> ">`_"
inlineToRST (Image alternate (source', tit)) = do
let source = unescapeURI source'
- pics <- get >>= (return . stImages)
+ pics <- get >>= return . stImages
let labelsUsed = map fst pics
- let txt = if null alternate || alternate == [Str ""] ||
+ let txt = if null alternate || alternate == [Str ""] ||
alternate `elem` labelsUsed
then [Str $ "image" ++ show (length pics)]
else alternate
@@ -333,10 +325,10 @@ inlineToRST (Image alternate (source', tit)) = do
else (txt, (source, tit)):pics
modify $ \st -> st { stImages = pics' }
label <- inlineListToRST txt
- return $ char '|' <> label <> char '|'
+ return $ "|" <> label <> "|"
inlineToRST (Note contents) = do
-- add to notes in state
- notes <- get >>= (return . stNotes)
+ notes <- get >>= return . stNotes
modify $ \st -> st { stNotes = contents:notes }
let ref = show $ (length notes) + 1
- return $ text " [" <> text ref <> text "]_"
+ return $ " [" <> text ref <> "]_"