aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Definition.hs8
-rw-r--r--src/Text/Pandoc/Entities.hs11
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs74
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs74
-rw-r--r--src/Text/Pandoc/Shared.hs92
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs78
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs266
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs43
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs23
-rw-r--r--src/Text/Pandoc/Writers/RST.hs8
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs8
11 files changed, 380 insertions, 305 deletions
diff --git a/src/Text/Pandoc/Definition.hs b/src/Text/Pandoc/Definition.hs
index acdec2de8..2313b1ef1 100644
--- a/src/Text/Pandoc/Definition.hs
+++ b/src/Text/Pandoc/Definition.hs
@@ -65,13 +65,21 @@ data Target
| Ref [Inline] -- ^ Label (list of inlines) for an indirect ref
deriving (Show, Eq, Read)
+-- | Type of quotation marks to use in Quoted inline.
+data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Read)
+
-- | Inline elements.
data Inline
= Str String -- ^ Text (string)
| Emph [Inline] -- ^ Emphasized text (list of inlines)
| Strong [Inline] -- ^ Strongly emphasized text (list of inlines)
+ | Quoted QuoteType [Inline] -- ^ Quoted text (list of inlines)
| Code String -- ^ Inline code (literal)
| Space -- ^ Inter-word space
+ | EmDash -- ^ Em dash
+ | EnDash -- ^ En dash
+ | Apostrophe -- ^ Apostrophe
+ | Ellipses -- ^ Ellipses
| LineBreak -- ^ Hard line break
| TeX String -- ^ LaTeX code (literal)
| HtmlInline String -- ^ HTML code (literal)
diff --git a/src/Text/Pandoc/Entities.hs b/src/Text/Pandoc/Entities.hs
index fd3cf9e57..26785b9a8 100644
--- a/src/Text/Pandoc/Entities.hs
+++ b/src/Text/Pandoc/Entities.hs
@@ -32,14 +32,19 @@ module Text.Pandoc.Entities (
entityToChar,
charToEntity,
decodeEntities,
- encodeEntities
+ encodeEntities,
+ characterEntity
) where
import Data.Char ( chr, ord )
-import Text.Regex ( mkRegex, matchRegexAll )
+import Text.Regex ( mkRegex, matchRegexAll, Regex )
import Maybe ( fromMaybe )
--- regexs for entities
+-- | Regular expression for decimal coded entity.
+decimalCodedEntity :: Text.Regex.Regex
decimalCodedEntity = mkRegex "&#([0-9]+);"
+
+-- | Regular expression for character entity.
+characterEntity :: Text.Regex.Regex
characterEntity = mkRegex "&#[0-9]+;|&[A-Za-z0-9]+;"
-- | Return a string with all entity references decoded to unicode characters
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index f82705bb2..9e966cc04 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -50,23 +50,12 @@ readLaTeX = readWith parseLaTeX
testString = testStringWith parseLaTeX
-- characters with special meaning
-specialChars = "\\$%&^&_~#{}\n \t|<>"
+specialChars = "\\$%&^&_~#{}\n \t|<>'\"-"
--
-- utility functions
--
--- | Change quotation marks in a string back to "basic" quotes.
-normalizeQuotes :: String -> String
-normalizeQuotes = gsub "''" "\"" . gsub "`" "'"
-
--- | Change LaTeX En dashes between digits to hyphens.
-normalizeDashes :: String -> String
-normalizeDashes = gsub "([0-9])--([0-9])" "\\1-\\2"
-
-normalizePunctuation :: String -> String
-normalizePunctuation = normalizeDashes . normalizeQuotes
-
-- | Returns text between brackets and its matching pair.
bracketedText openB closeB = try (do
char openB
@@ -132,10 +121,10 @@ anyEnvironment = try (do
--
-- | Process LaTeX preamble, extracting metadata.
-processLaTeXPreamble = do
+processLaTeXPreamble = try (do
manyTill (choice [bibliographic, comment, unknownCommand, nullBlock])
(try (string "\\begin{document}"))
- spaces
+ spaces)
-- | Parse LaTeX and return 'Pandoc'.
parseLaTeX = do
@@ -392,16 +381,13 @@ comment = try (do
-- inline
--
-inline = choice [ strong, emph, ref, lab, code, linebreak, math, ldots,
+inline = choice [ strong, emph, ref, lab, code, linebreak, math, ellipses,
+ emDash, enDash, hyphen, quoted, apostrophe,
accentedChar, specialChar, specialInline, escapedChar,
unescapedChar, str, endline, whitespace ] <?> "inline"
-specialInline = choice [ link, image, footnote, rawLaTeXInline ] <?>
- "link, raw TeX, note, or image"
-
-ldots = try (do
- string "\\ldots"
- return (Str "..."))
+specialInline = choice [ link, image, footnote, rawLaTeXInline ]
+ <?> "link, raw TeX, note, or image"
accentedChar = normalAccentedChar <|> specialAccentedChar
@@ -526,6 +512,49 @@ emph = try (do
result <- manyTill inline (char '}')
return (Emph result))
+apostrophe = do
+ char '\''
+ return Apostrophe
+
+quoted = do
+ doubleQuoted <|> singleQuoted
+
+singleQuoted = try (do
+ result <- enclosed singleQuoteStart singleQuoteEnd inline
+ return $ Quoted SingleQuote $ normalizeSpaces result)
+
+doubleQuoted = try (do
+ result <- enclosed doubleQuoteStart doubleQuoteEnd inline
+ return $ Quoted DoubleQuote $ normalizeSpaces result)
+
+singleQuoteStart = char '`'
+
+singleQuoteEnd = try (do
+ char '\''
+ notFollowedBy alphaNum)
+
+doubleQuoteStart = try (string "``")
+
+doubleQuoteEnd = try (string "''")
+
+ellipses = try (do
+ string "\\ldots"
+ option "" (string "{}")
+ return Ellipses)
+
+enDash = try (do
+ string "--"
+ notFollowedBy (char '-')
+ return EnDash)
+
+emDash = try (do
+ string "---"
+ return EmDash)
+
+hyphen = do
+ char '-'
+ return (Str "-")
+
lab = try (do
string "\\label{"
result <- manyTill anyChar (char '}')
@@ -552,7 +581,7 @@ linebreak = try (do
str = do
result <- many1 (noneOf specialChars)
- return (Str (normalizePunctuation result))
+ return (Str result)
-- endline internal to paragraph
endline = try (do
@@ -624,3 +653,4 @@ rawLaTeXInline = try (do
then fail "not an inline command"
else string ""
return (TeX ("\\" ++ name ++ star ++ argStr)))
+
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 30d6a11df..7fab2ad01 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -86,12 +86,13 @@ titleOpeners = "\"'("
setextHChars = ['=','-']
blockQuoteChar = '>'
hyphenChar = '-'
+ellipsesChar = '.'
-- treat these as potentially non-text when parsing inline:
specialChars = [escapeChar, labelStart, labelEnd, emphStart, emphEnd,
emphStartAlt, emphEndAlt, codeStart, codeEnd, autoLinkEnd,
autoLinkStart, mathStart, mathEnd, imageStart, noteStart,
- hyphenChar]
+ hyphenChar, ellipsesChar] ++ quoteChars
--
-- auxiliary functions
@@ -120,6 +121,11 @@ failUnlessBeginningOfLine = do
pos <- getPosition
if sourceColumn pos == 1 then return () else fail "not beginning of line"
+-- | Fail unless we're in "smart typography" mode.
+failUnlessSmart = do
+ state <- getState
+ if stateSmart state then return () else fail "Smart typography feature"
+
--
-- document structure
--
@@ -519,11 +525,11 @@ rawLaTeXEnvironment' = do
-- inline
--
-text = choice [ math, strong, emph, code, str, linebreak, tabchar,
- whitespace, endline ] <?> "text"
+text = choice [ escapedChar, math, strong, emph, smartPunctuation,
+ code, ltSign, symbol,
+ str, linebreak, tabchar, whitespace, endline ] <?> "text"
-inline = choice [ rawLaTeXInline', escapedChar, special, hyphens, text,
- ltSign, symbol ] <?> "inline"
+inline = choice [ rawLaTeXInline', escapedChar, special, text ] <?> "inline"
special = choice [ noteRef, inlineNote, link, referenceLink, rawHtmlInline',
autoLink, image ] <?> "link, inline html, note, or image"
@@ -531,6 +537,7 @@ special = choice [ noteRef, inlineNote, link, referenceLink, rawHtmlInline',
escapedChar = escaped anyChar
ltSign = try (do
+ notFollowedBy (noneOf "<") -- continue only if it's a <
notFollowedBy' rawHtmlBlocks -- don't return < if it starts html
char '<'
return (Str ['<']))
@@ -541,13 +548,6 @@ symbol = do
result <- oneOf specialCharsMinusLt
return (Str [result])
-hyphens = try (do
- result <- many1 (char '-')
- if (length result) == 1
- then skipEndline -- don't want to treat endline after hyphen as a space
- else do{ string ""; return Space }
- return (Str result))
-
-- parses inline code, between n codeStarts and n codeEnds
code = try (do
starts <- many1 (char codeStart)
@@ -583,6 +583,56 @@ strong = do
(count 2 (char emphEndAlt)) inline) ]
return (Strong (normalizeSpaces result))
+smartPunctuation = do
+ failUnlessSmart
+ choice [ quoted, apostrophe, dash, ellipses ]
+
+apostrophe = do
+ char '\'' <|> char '\8217'
+ return Apostrophe
+
+quoted = do
+ doubleQuoted <|> singleQuoted
+
+singleQuoted = try (do
+ result <- enclosed singleQuoteStart singleQuoteEnd
+ (do{notFollowedBy' singleQuoted; inline} <|> apostrophe)
+ return $ Quoted SingleQuote $ normalizeSpaces result)
+
+doubleQuoted = try (do
+ result <- enclosed doubleQuoteStart doubleQuoteEnd inline
+ return $ Quoted DoubleQuote $ normalizeSpaces result)
+
+singleQuoteStart = try (do
+ char '\'' <|> char '\8216'
+ notFollowedBy' whitespace)
+
+singleQuoteEnd = try (do
+ oneOfStrings ["'", "\8217"]
+ notFollowedBy alphaNum)
+
+doubleQuoteStart = char '"' <|> char '\8220'
+
+doubleQuoteEnd = char '"' <|> char '\8221'
+
+ellipses = try (do
+ oneOfStrings ["...", " . . . ", ". . .", " . . ."]
+ return Ellipses)
+
+dash = enDash <|> emDash
+
+enDash = try (do
+ char '-'
+ followedBy' (many1 digit)
+ return EnDash)
+
+emDash = try (do
+ skipSpaces
+ oneOfStrings ["---", "--"]
+ skipSpaces
+ option ' ' newline
+ return EmDash)
+
whitespace = do
many1 (oneOf spaceChars) <?> "whitespace"
return Space
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index da00bb8c4..91b44e6bf 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -52,7 +52,6 @@ module Text.Pandoc.Shared (
-- * Native format prettyprinting
prettyPandoc,
-- * Pandoc block list processing
- consolidateList,
isNoteBlock,
normalizeSpaces,
compactify,
@@ -74,7 +73,7 @@ module Text.Pandoc.Shared (
) where
import Text.Pandoc.Definition
import Text.ParserCombinators.Parsec
-import Text.Pandoc.Entities ( decodeEntities, encodeEntities )
+import Text.Pandoc.Entities ( decodeEntities, encodeEntities, characterEntity )
import Text.Regex ( matchRegexAll, mkRegex, subRegex, Regex )
import Text.PrettyPrint.HughesPJ as PP ( text, char, (<>), ($$), nest, Doc,
isEmpty )
@@ -125,6 +124,7 @@ data ParserState = ParserState
stateAuthors :: [String], -- ^ Authors of document
stateDate :: String, -- ^ Date of document
stateStrict :: Bool, -- ^ Use strict markdown syntax
+ stateSmart :: Bool, -- ^ Use smart typography
stateHeaderTable :: [HeaderType] -- ^ List of header types used,
-- in what order (rst only)
}
@@ -144,19 +144,9 @@ defaultParserState =
stateAuthors = [],
stateDate = [],
stateStrict = False,
+ stateSmart = False,
stateHeaderTable = [] }
--- | Consolidate @Str@s and @Space@s in an inline list into one big @Str@.
--- Collapse adjacent @Space@s.
-consolidateList :: [Inline] -> [Inline]
-consolidateList ((Str a):(Str b):rest) = consolidateList ((Str (a ++ b)):rest)
-consolidateList ((Str a):Space:Space:rest) = consolidateList ((Str a):Space:rest)
-consolidateList ((Str a):Space:rest) = consolidateList ((Str (a ++ " ")):rest)
-consolidateList (Space:(Str a):rest) = consolidateList ((Str (" " ++ a)):rest)
-consolidateList (Space:Space:rest) = consolidateList ((Str " "):rest)
-consolidateList (inline:rest) = inline:(consolidateList rest)
-consolidateList [] = []
-
-- | Indent string as a block.
indentBy :: Int -- ^ Number of spaces to indent the block
-> Int -- ^ Number of spaces (rel to block) to indent first line
@@ -341,7 +331,6 @@ data WriterOptions = WriterOptions
, writerHeader :: String -- ^ Header for the document
, writerIncludeBefore :: String -- ^ String to include before the body
, writerIncludeAfter :: String -- ^ String to include after the body
- , writerSmart :: Bool -- ^ Use smart typography
, writerS5 :: Bool -- ^ We're writing S5
, writerIncremental :: Bool -- ^ Incremental S5 lists
, writerNumberSections :: Bool -- ^ Number sections in LaTeX
@@ -463,6 +452,8 @@ refsMatch ((Emph x):restx) ((Emph y):resty) =
refsMatch x y && refsMatch restx resty
refsMatch ((Strong x):restx) ((Strong y):resty) =
refsMatch x y && refsMatch restx resty
+refsMatch ((Quoted t x):restx) ((Quoted u y):resty) =
+ t == u && refsMatch x y && refsMatch restx resty
refsMatch (x:restx) (y:resty) = (x == y) && refsMatch restx resty
refsMatch [] x = null x
refsMatch x [] = null x
@@ -517,48 +508,14 @@ replaceRefLinksInline keytable (Emph lst) =
Emph (map (replaceRefLinksInline keytable) lst)
replaceRefLinksInline keytable (Strong lst) =
Strong (map (replaceRefLinksInline keytable) lst)
+replaceRefLinksInline keytable (Quoted t lst) =
+ Quoted t (map (replaceRefLinksInline keytable) lst)
replaceRefLinksInline keytable other = other
--- | Escape string, preserving character entities and quote, and adding
--- smart typography if specified.
-stringToSGML :: WriterOptions -> String -> String
-stringToSGML options =
- let escapeDoubleQuotes =
- gsub "(\"|&quot;)" "&rdquo;" . -- rest are right quotes
- gsub "(\"|&quot;)(&r[sd]quo;)" "&rdquo;\\2" .
- -- never left quo before right quo
- gsub "(&l[sd]quo;)(\"|&quot;)" "\\2&ldquo;" .
- -- never right quo after left quo
- gsub "([ \t])(\"|&quot;)" "\\1&ldquo;" .
- -- never right quo after space
- gsub "(\"|&quot;)([^,.;:!?^) \t-])" "&ldquo;\\2" . -- "word left
- gsub "(\"|&quot;)('|`|&lsquo;)" "&rdquo;&rsquo;" .
- -- right if it got through last filter
- gsub "(\"|&quot;)('|`|&lsquo;)([^,.;:!?^) \t-])" "&ldquo;&lsquo;\\3" .
- -- "'word left
- gsub "``" "&ldquo;" .
- gsub "''" "&rdquo;"
- escapeSingleQuotes =
- gsub "'" "&rsquo;" . -- otherwise right
- gsub "'(&r[sd]quo;)" "&rsquo;\\1" . -- never left quo before right quo
- gsub "(&l[sd]quo;)'" "\\1&lsquo;" . -- never right quo after left quo
- gsub "([ \t])'" "\\1&lsquo;" . -- never right quo after space
- gsub "`" "&lsquo;" . -- ` is left
- gsub "([^,.;:!?^) \t-])'" "\\1&rsquo;" . -- word' right
- gsub "^('|`)([^,.;:!?^) \t-])" "&lsquo;\\2" . -- 'word left
- gsub "('|`)(\"|&quot;|&ldquo;|``)" "&lsquo;&ldquo;" . -- '"word left
- gsub "([^,.;:!?^) \t-])'(s|S)" "\\1&rsquo;\\2" . -- possessive
- gsub "([[:space:]])'([^,.;:!?^) \t-])" "\\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;"
- smartFilter = escapeSingleQuotes . escapeDoubleQuotes . escapeDashes .
- escapeEllipses in
- encodeEntities . (if (writerSmart options) then smartFilter else id) .
- (escapePreservingRegex escapeSGML (mkRegex "&[[:alnum:]]*;"))
+-- | Escape string, preserving character entities.
+stringToSGML :: String -> String
+stringToSGML =
+ encodeEntities . (escapePreservingRegex escapeSGML characterEntity)
-- | Escape string as needed for HTML. Entity references are not preserved.
escapeSGML :: String -> String
@@ -571,16 +528,15 @@ escapeSGML (x:xs) = case x of
_ -> x:(escapeSGML xs)
-- | Return a text object with a string of formatted SGML attributes.
-attributeList :: WriterOptions -> [(String, String)] -> Doc
-attributeList options =
- text . concatMap (\(a, b) -> " " ++ stringToSGML options a ++ "=\"" ++
- stringToSGML options b ++ "\"")
+attributeList :: [(String, String)] -> Doc
+attributeList = text . concatMap
+ (\(a, b) -> " " ++ stringToSGML a ++ "=\"" ++ stringToSGML b ++ "\"")
-- | Put the supplied contents between start and end tags of tagType,
-- with specified attributes and (if specified) indentation.
-inTags:: Bool -> WriterOptions -> String -> [(String, String)] -> Doc -> Doc
-inTags isIndented options tagType attribs contents =
- let openTag = PP.char '<' <> text tagType <> attributeList options attribs <>
+inTags:: Bool -> String -> [(String, String)] -> Doc -> Doc
+inTags isIndented tagType attribs contents =
+ let openTag = PP.char '<' <> text tagType <> attributeList attribs <>
PP.char '>'
closeTag = text "</" <> text tagType <> PP.char '>' in
if isIndented
@@ -588,15 +544,15 @@ inTags isIndented options tagType attribs contents =
else openTag <> contents <> closeTag
-- | Return a self-closing tag of tagType with specified attributes
-selfClosingTag :: WriterOptions -> String -> [(String, String)] -> Doc
-selfClosingTag options tagType attribs =
- PP.char '<' <> text tagType <> attributeList options attribs <> text " />"
+selfClosingTag :: String -> [(String, String)] -> Doc
+selfClosingTag tagType attribs =
+ PP.char '<' <> text tagType <> attributeList attribs <> text " />"
-- | Put the supplied contents between start and end tags of tagType.
-inTagsSimple :: WriterOptions -> String -> Doc -> Doc
-inTagsSimple options tagType = inTags False options tagType []
+inTagsSimple :: String -> Doc -> Doc
+inTagsSimple tagType = inTags False tagType []
-- | Put the supplied contents in indented block btw start and end tags.
-inTagsIndented :: WriterOptions -> String -> Doc -> Doc
-inTagsIndented options tagType = inTags True options tagType []
+inTagsIndented :: String -> Doc -> Doc
+inTagsIndented tagType = inTags True tagType []
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 0fa4a1d98..29fdf965f 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -59,14 +59,14 @@ hierarchicalize (block:rest) =
x -> (Blk x):(hierarchicalize rest)
-- | Convert list of authors to a docbook <author> section
-authorToDocbook :: WriterOptions -> [Char] -> Doc
-authorToDocbook opts name = inTagsIndented opts "author" $
+authorToDocbook :: [Char] -> Doc
+authorToDocbook name = inTagsIndented "author" $
if ',' `elem` name
then -- last name first
let (lastname, rest) = break (==',') name
firstname = removeLeadingSpace rest in
- inTagsSimple opts "firstname" (text $ stringToSGML opts firstname) <>
- inTagsSimple opts "surname" (text $ stringToSGML opts lastname)
+ inTagsSimple "firstname" (text $ stringToSGML firstname) <>
+ inTagsSimple "surname" (text $ stringToSGML lastname)
else -- last name last
let namewords = words name
lengthname = length namewords
@@ -74,8 +74,8 @@ authorToDocbook opts name = inTagsIndented opts "author" $
0 -> ("","")
1 -> ("", name)
n -> (joinWithSep " " (take (n-1) namewords), last namewords) in
- inTagsSimple opts "firstname" (text $ stringToSGML opts firstname) $$
- inTagsSimple opts "surname" (text $ stringToSGML opts lastname)
+ inTagsSimple "firstname" (text $ stringToSGML firstname) $$
+ inTagsSimple "surname" (text $ stringToSGML lastname)
-- | Convert Pandoc document to string in Docbook format.
writeDocbook :: WriterOptions -> Pandoc -> String
@@ -84,22 +84,24 @@ writeDocbook opts (Pandoc (Meta title authors date) blocks) =
then text (writerHeader opts)
else empty
meta = if (writerStandalone opts)
- then inTagsIndented opts "articleinfo" $
- (inTagsSimple opts "title" (inlinesToDocbook opts title)) $$
- (vcat (map (authorToDocbook opts) authors)) $$
- (inTagsSimple opts "date" (text $ stringToSGML opts date))
+ then inTagsIndented "articleinfo" $
+ (inTagsSimple "title" (wrap opts title)) $$
+ (vcat (map authorToDocbook authors)) $$
+ (inTagsSimple "date" (text $ stringToSGML date))
else empty
blocks' = replaceReferenceLinks blocks
(noteBlocks, blocks'') = partition isNoteBlock blocks'
opts' = opts {writerNotes = noteBlocks}
elements = hierarchicalize blocks''
- body = text (writerIncludeBefore opts') <>
+ before = writerIncludeBefore opts'
+ after = writerIncludeAfter opts'
+ body = (if null before then empty else text before) $$
vcat (map (elementToDocbook opts') elements) $$
- text (writerIncludeAfter opts')
+ (if null after then empty else text after)
body' = if writerStandalone opts'
- then inTagsIndented opts "article" (meta $$ body)
+ then inTagsIndented "article" (meta $$ body)
else body in
- render $ head $$ body' <> text "\n"
+ render $ head $$ body' $$ text ""
-- | Convert an Element to Docbook.
elementToDocbook :: WriterOptions -> Element -> Doc
@@ -109,8 +111,8 @@ elementToDocbook opts (Sec title elements) =
let elements' = if null elements
then [Blk (Para [])]
else elements in
- inTagsIndented opts "section" $
- inTagsSimple opts "title" (wrap opts title) $$
+ inTagsIndented "section" $
+ inTagsSimple "title" (wrap opts title) $$
vcat (map (elementToDocbook opts) elements')
-- | Convert a list of Pandoc blocks to Docbook.
@@ -128,7 +130,7 @@ listItemToDocbook opts item =
let plainToPara (Plain x) = Para x
plainToPara y = y in
let item' = map plainToPara item in
- inTagsIndented opts "listitem" (blocksToDocbook opts item')
+ inTagsIndented "listitem" (blocksToDocbook opts item')
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc
@@ -136,20 +138,20 @@ blockToDocbook opts Blank = text ""
blockToDocbook opts Null = empty
blockToDocbook opts (Plain lst) = wrap opts lst
blockToDocbook opts (Para lst) =
- inTagsIndented opts "para" (wrap opts lst)
+ inTagsIndented "para" (wrap opts lst)
blockToDocbook opts (BlockQuote blocks) =
- inTagsIndented opts "blockquote" (blocksToDocbook opts blocks)
+ inTagsIndented "blockquote" (blocksToDocbook opts blocks)
blockToDocbook opts (CodeBlock str) =
text "<screen>\n" <> text (escapeSGML str) <> text "\n</screen>"
blockToDocbook opts (BulletList lst) =
- inTagsIndented opts "itemizedlist" $ listItemsToDocbook opts lst
+ inTagsIndented "itemizedlist" $ listItemsToDocbook opts lst
blockToDocbook opts (OrderedList lst) =
- inTagsIndented opts "orderedlist" $ listItemsToDocbook opts lst
+ inTagsIndented "orderedlist" $ listItemsToDocbook opts lst
blockToDocbook opts (RawHtml str) = text str -- raw XML block
blockToDocbook opts HorizontalRule = empty -- not semantic
blockToDocbook opts (Note _ _) = empty -- shouldn't occur
blockToDocbook opts (Key _ _) = empty -- shouldn't occur
-blockToDocbook opts _ = inTagsIndented opts "para" (text "Unknown block type")
+blockToDocbook opts _ = inTagsIndented "para" (text "Unknown block type")
-- | Put string in CDATA section
cdata :: String -> Doc
@@ -165,14 +167,20 @@ inlinesToDocbook opts lst = hcat (map (inlineToDocbook opts) lst)
-- | Convert an inline element to Docbook.
inlineToDocbook :: WriterOptions -> Inline -> Doc
-inlineToDocbook opts (Str str) = text $ stringToSGML opts str
+inlineToDocbook opts (Str str) = text $ stringToSGML str
inlineToDocbook opts (Emph lst) =
- inTagsSimple opts "emphasis" (inlinesToDocbook opts lst)
+ inTagsSimple "emphasis" (inlinesToDocbook opts lst)
inlineToDocbook opts (Strong lst) =
- inTags False opts "emphasis" [("role", "strong")]
+ inTags False "emphasis" [("role", "strong")]
(inlinesToDocbook opts lst)
+inlineToDocbook opts (Quoted _ lst) =
+ inTagsSimple "quote" (inlinesToDocbook opts lst)
+inlineToDocbook opts Apostrophe = text "&apos;"
+inlineToDocbook opts Ellipses = text "&hellip;"
+inlineToDocbook opts EmDash = text "&mdash;"
+inlineToDocbook opts EnDash = text "&ndash;"
inlineToDocbook opts (Code str) =
- inTagsSimple opts "literal" $ text (escapeSGML str)
+ inTagsSimple "literal" $ text (escapeSGML str)
inlineToDocbook opts (TeX str) = inlineToDocbook opts (Code str)
inlineToDocbook opts (HtmlInline str) = empty
inlineToDocbook opts LineBreak =
@@ -180,19 +188,19 @@ inlineToDocbook opts LineBreak =
inlineToDocbook opts Space = char ' '
inlineToDocbook opts (Link txt (Src src tit)) =
case (matchRegex (mkRegex "mailto:(.*)") src) of
- Just [addr] -> inTagsSimple opts "email" $ text (escapeSGML addr)
- Nothing -> inTags False opts "ulink" [("url", src)] $
+ Just [addr] -> inTagsSimple "email" $ text (escapeSGML addr)
+ Nothing -> inTags False "ulink" [("url", src)] $
inlinesToDocbook opts txt
inlineToDocbook opts (Link text (Ref ref)) = empty -- shouldn't occur
inlineToDocbook opts (Image alt (Src src tit)) =
let titleDoc = if null tit
then empty
- else inTagsIndented opts "objectinfo" $
- inTagsIndented opts "title"
- (text $ stringToSGML opts tit) in
- inTagsIndented opts "inlinemediaobject" $
- inTagsIndented opts "imageobject" $
- titleDoc $$ selfClosingTag opts "imagedata" [("fileref", src)]
+ else inTagsIndented "objectinfo" $
+ inTagsIndented "title"
+ (text $ stringToSGML tit) in
+ inTagsIndented "inlinemediaobject" $
+ inTagsIndented "imageobject" $
+ titleDoc $$ selfClosingTag "imagedata" [("fileref", src)]
inlineToDocbook opts (Image alternate (Ref ref)) = empty --shouldn't occur
inlineToDocbook opts (NoteRef ref) =
let notes = writerNotes opts
@@ -200,4 +208,4 @@ inlineToDocbook opts (NoteRef ref) =
if null hits
then empty
else let (Note _ contents) = head hits in
- inTagsIndented opts "footnote" $ blocksToDocbook opts contents
+ inTagsIndented "footnote" $ blocksToDocbook opts contents
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index b42d78eb0..4c869ac21 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -37,48 +37,53 @@ import Text.Regex ( mkRegex, matchRegex )
import Numeric ( showHex )
import Data.Char ( ord, toLower )
import Data.List ( isPrefixOf, partition )
+import Text.PrettyPrint.HughesPJ hiding ( Str )
-- | 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
+writeHtml opts (Pandoc (Meta title authors date) blocks) =
+ let titlePrefix = writerTitlePrefix opts 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))
+ let head = if (writerStandalone opts)
+ then htmlHeader opts (Meta topTitle authors date)
+ else empty
+ titleBlocks = if (writerStandalone opts) && (not (null title)) &&
+ (not (writerS5 opts))
then [RawHtml "<h1 class=\"title\">", Plain title,
- RawHtml "</h1>\n"]
+ RawHtml "</h1>"]
else []
- foot = if (writerStandalone options) then "</body>\n</html>\n" else ""
+ foot = if (writerStandalone opts)
+ then text "</body>\n</html>"
+ else empty
blocks' = replaceReferenceLinks (titleBlocks ++ blocks)
(noteBlocks, blocks'') = partition isNoteBlock blocks'
- body = (writerIncludeBefore options) ++
- concatMap (blockToHtml options) blocks'' ++
- footnoteSection options noteBlocks ++
- (writerIncludeAfter options) in
- head ++ body ++ foot
+ before = writerIncludeBefore opts
+ after = writerIncludeAfter opts
+ body = (if null before then empty else text before) $$
+ vcat (map (blockToHtml opts) blocks'') $$
+ footnoteSection opts noteBlocks $$
+ (if null after then empty else text after) in
+ render $ head $$ body $$ foot $$ text ""
-- | Convert list of Note blocks to a footnote <div>.
-- Assumes notes are sorted.
-footnoteSection :: WriterOptions -> [Block] -> String
-footnoteSection options notes =
+footnoteSection :: WriterOptions -> [Block] -> Doc
+footnoteSection opts notes =
if null notes
- then ""
- else "<div class=\"footnotes\">\n<hr />\n<ol>\n" ++
- concatMap (blockToHtml options) notes ++
- "</ol>\n</div>\n"
+ then empty
+ else inTags True "div" [("class","footnotes")] $
+ selfClosingTag "hr" [] $$ (inTagsIndented "ol"
+ (vcat $ map (blockToHtml opts) notes))
-- | Obfuscate a "mailto:" link using Javascript.
-obfuscateLink :: WriterOptions -> [Inline] -> String -> String
-obfuscateLink options text src =
+obfuscateLink :: WriterOptions -> [Inline] -> String -> Doc
+obfuscateLink opts txt src =
let emailRegex = mkRegex "mailto:*([^@]*)@(.*)"
- text' = inlineListToHtml options text
+ text' = render $ inlineListToHtml opts txt
src' = map toLower src in
case (matchRegex emailRegex src') of
(Just [name, domain]) ->
@@ -91,16 +96,17 @@ obfuscateLink options text src =
then name ++ " at " ++ domain'
else text' ++ " (" ++ name ++ " at " ++
domain' ++ ")" in
- if writerStrictMarkdown options
- then "<a href=\"" ++ obfuscateString src' ++ "\">" ++
- obfuscateString text' ++ "</a>"
- else "<script type=\"text/javascript\">\n<!--\nh='" ++
+ if writerStrictMarkdown opts
+ then inTags False "a" [("href", obfuscateString src')] $
+ text $ obfuscateString text'
+ else inTags False "script" [("type", "text/javascript")]
+ (text ("\n<!--\nh='" ++
obfuscateString domain ++ "';a='" ++ at' ++ "';n='" ++
obfuscateString name ++ "';e=n+a+h;\n" ++
"document.write('<a h'+'ref'+'=\"ma'+'ilto'+':'+e+'\">'+" ++
- linkText ++ "+'<\\/'+'a'+'>');\n// -->\n</script><noscript>" ++
- obfuscateString altText ++ "</noscript>"
- _ -> "<a href=\"" ++ src ++ "\">" ++ text' ++ "</a>" -- malformed email
+ linkText ++ "+'<\\/'+'a'+'>');\n// -->\n")) <>
+ inTagsSimple "noscript" (text (obfuscateString altText))
+ _ -> inTags False "a" [("href", src)] (text text') -- malformed email
-- | Obfuscate character as entity.
obfuscateChar :: Char -> String
@@ -113,117 +119,123 @@ obfuscateChar char =
obfuscateString :: String -> String
obfuscateString = concatMap obfuscateChar
--- | Returns an HTML header with appropriate bibliographic information.
-htmlHeader :: WriterOptions -> Meta -> String
-htmlHeader options (Meta title authors date) =
- let titletext = "<title>" ++ (inlineListToHtml options title) ++
- "</title>\n"
+-- | Return an HTML header with appropriate bibliographic information.
+htmlHeader :: WriterOptions -> Meta -> Doc
+htmlHeader opts (Meta title authors date) =
+ let titletext = inTagsSimple "title" (wrap opts title)
authortext = if (null authors)
- then ""
- else "<meta name=\"author\" content=\"" ++
- (joinWithSep ", " (map (stringToSGML options) authors)) ++
- "\" />\n"
+ then empty
+ else selfClosingTag "meta" [("name", "author"),
+ ("content",
+ joinWithSep ", " (map stringToSGML authors))]
datetext = if (date == "")
- then ""
- else "<meta name=\"date\" content=\"" ++
- (stringToSGML options date) ++ "\" />\n" in
- (writerHeader options) ++ authortext ++ datetext ++ titletext ++
- "</head>\n<body>\n"
+ then empty
+ else selfClosingTag "meta" [("name", "date"),
+ ("content", stringToSGML date)] in
+ text (writerHeader opts) $$ authortext $$ datetext $$ titletext $$
+ text "</head>\n<body>"
+
+-- | Take list of inline elements and return wrapped doc.
+wrap :: WriterOptions -> [Inline] -> Doc
+wrap opts lst = fsep $ map (inlineListToHtml opts) (splitBy Space lst)
-- | 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)
+blockToHtml :: WriterOptions -> Block -> Doc
+blockToHtml opts Blank = text ""
+blockToHtml opts Null = empty
+blockToHtml opts (Plain lst) = wrap opts lst
+blockToHtml opts (Para lst) = inTagsIndented "p" $ wrap opts lst
+blockToHtml opts (BlockQuote blocks) =
+ if (writerS5 opts)
then -- in S5, treat list in blockquote specially
-- if default is incremental, make it nonincremental;
-- otherwise incremental
- let inc = not (writerIncremental options) in
+ let inc = not (writerIncremental opts) in
case blocks of
- [BulletList lst] -> blockToHtml (options {writerIncremental =
+ [BulletList lst] -> blockToHtml (opts {writerIncremental =
inc}) (BulletList lst)
- [OrderedList lst] -> blockToHtml (options {writerIncremental =
+ [OrderedList lst] -> blockToHtml (opts {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 contents = (concatMap (blockToHtml options) lst) in
- "<li id=\"fn" ++ ref ++ "\">" ++ contents ++ " <a href=\"#fnref" ++ ref ++
- "\" class=\"footnoteBacklink\" title=\"Jump back to footnote " ++ ref ++
- "\">&#8617;</a></li>\n"
-blockToHtml options (Key _ _) = ""
-blockToHtml options (CodeBlock str) =
- "<pre><code>" ++ (escapeSGML str) ++ "\n</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) =
- let contents = inlineListToHtml options lst in
+ otherwise -> inTagsIndented "blockquote" $
+ vcat $ map (blockToHtml opts) blocks
+ else inTagsIndented "blockquote" $ vcat $ map (blockToHtml opts) blocks
+blockToHtml opts (Note ref lst) =
+ let contents = (vcat $ map (blockToHtml opts) lst) in
+ inTags True "li" [("id", "fn" ++ ref)] $
+ contents <> inTags False "a" [("href", "#fnref" ++ ref),
+ ("class", "footnoteBacklink"),
+ ("title", "Jump back to footnote " ++ ref)]
+ (text "&#8617;")
+blockToHtml opts (Key _ _) = empty
+blockToHtml opts (CodeBlock str) =
+ text "<pre><code>" <> text (escapeSGML str) <> text "\n</code></pre>"
+blockToHtml opts (RawHtml str) = text str
+blockToHtml opts (BulletList lst) =
+ let attribs = if (writerIncremental opts)
+ then [("class","incremental")]
+ else [] in
+ inTags True "ul" attribs $ vcat $ map (listItemToHtml opts) lst
+blockToHtml opts (OrderedList lst) =
+ let attribs = if (writerIncremental opts)
+ then [("class","incremental")]
+ else [] in
+ inTags True "ol" attribs $ vcat $ map (listItemToHtml opts) lst
+blockToHtml opts HorizontalRule = selfClosingTag "hr" []
+blockToHtml opts (Header level lst) =
+ let contents = wrap opts lst in
if ((level > 0) && (level <= 6))
- then "<h" ++ (show level) ++ ">" ++ contents ++
- "</h" ++ (show level) ++ ">\n"
- else "<p>" ++ contents ++ "</p>\n"
-listItemToHtml options list =
- "<li>" ++ (concatMap (blockToHtml options) list) ++ "</li>\n"
+ then inTagsSimple ("h" ++ show level) contents
+ else inTagsSimple "p" contents
+
+listItemToHtml :: WriterOptions -> [Block] -> Doc
+listItemToHtml opts list =
+ inTagsSimple "li" $ vcat $ map (blockToHtml opts) list
-- | Convert list of Pandoc inline elements to HTML.
-inlineListToHtml :: WriterOptions -> [Inline] -> String
-inlineListToHtml options lst =
- -- consolidate adjacent Str and Space elements for more intelligent
- -- smart typography filtering
- let lst' = consolidateList lst in
- concatMap (inlineToHtml options) lst'
+inlineListToHtml :: WriterOptions -> [Inline] -> Doc
+inlineListToHtml opts lst = hcat (map (inlineToHtml opts) 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>" ++ (escapeSGML str) ++ "</code>"
-inlineToHtml options (Str str) = stringToSGML options str
-inlineToHtml options (TeX str) = (escapeSGML str)
-inlineToHtml options (HtmlInline str) = str
-inlineToHtml options (LineBreak) = "<br />\n"
-inlineToHtml options Space = " "
-inlineToHtml options (Link text (Src src tit)) =
- let title = stringToSGML options tit in
+inlineToHtml :: WriterOptions -> Inline -> Doc
+inlineToHtml opts (Emph lst) =
+ inTagsSimple "em" (inlineListToHtml opts lst)
+inlineToHtml opts (Strong lst) =
+ inTagsSimple "strong" (inlineListToHtml opts lst)
+inlineToHtml opts (Code str) =
+ inTagsSimple "code" $ text (escapeSGML str)
+inlineToHtml opts (Quoted SingleQuote lst) =
+ text "&lsquo;" <> (inlineListToHtml opts lst) <> text "&rsquo;"
+inlineToHtml opts (Quoted DoubleQuote lst) =
+ text "&ldquo;" <> (inlineListToHtml opts lst) <> text "&rdquo;"
+inlineToHtml opts EmDash = text "&mdash;"
+inlineToHtml opts EnDash = text "&ndash;"
+inlineToHtml opts Ellipses = text "&hellip;"
+inlineToHtml opts Apostrophe = text "&rsquo;"
+inlineToHtml opts (Str str) = text $ stringToSGML str
+inlineToHtml opts (TeX str) = text $ escapeSGML str
+inlineToHtml opts (HtmlInline str) = text str
+inlineToHtml opts (LineBreak) = selfClosingTag "br" []
+inlineToHtml opts Space = space
+inlineToHtml opts (Link txt (Src src tit)) =
+ let title = stringToSGML tit in
if (isPrefixOf "mailto:" src)
- then obfuscateLink options text src
- else "<a href=\"" ++ (escapeSGML src) ++ "\"" ++
- (if tit /= "" then " title=\"" ++ title ++ "\">" else ">") ++
- (inlineListToHtml options text) ++ "</a>"
-inlineToHtml options (Link text (Ref ref)) =
- "[" ++ (inlineListToHtml options text) ++ "][" ++
- (inlineListToHtml options ref) ++ "]"
+ then obfuscateLink opts txt src
+ else inTags False "a" ([("href", escapeSGML src)] ++
+ if null tit then [] else [("title", title)])
+ (inlineListToHtml opts txt)
+inlineToHtml opts (Link txt (Ref ref)) =
+ char '[' <> (inlineListToHtml opts txt) <> text "][" <>
+ (inlineListToHtml opts ref) <> char ']'
-- this is what markdown does, for better or worse
-inlineToHtml options (Image alt (Src source tit)) =
- let title = stringToSGML options 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 ref)) =
- "![" ++ (inlineListToHtml options alternate) ++ "][" ++
- (inlineListToHtml options ref) ++ "]"
-inlineToHtml options (NoteRef ref) =
- "<sup class=\"footnoteRef\" id=\"fnref" ++ ref ++ "\"><a href=\"#fn" ++
- ref ++ "\">" ++ ref ++ "</a></sup>"
+inlineToHtml opts (Image alt (Src source tit)) =
+ let title = stringToSGML tit
+ alternate = render $ inlineListToHtml opts alt in
+ selfClosingTag "img" $ [("src", source)] ++
+ (if null tit then [] else [("title", title)]) ++
+ (if null alternate then [] else [("alt", alternate)])
+inlineToHtml opts (Image alternate (Ref ref)) =
+ text "![" <> (inlineListToHtml opts alternate) <> text "][" <>
+ (inlineListToHtml opts ref) <> char ']'
+inlineToHtml opts (NoteRef ref) =
+ inTags False "sup" [("class", "footnoteRef"), ("id", "fnref" ++ ref)]
+ (inTags False "a" [("href", "#fn" ++ ref)] $ text ref)
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index e34b7b61e..aca72535d 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -84,36 +84,9 @@ escapeBar = gsub "\\|" "\\\\textbar{}"
escapeLt = gsub "<" "\\\\textless{}"
escapeGt = gsub ">" "\\\\textgreater{}"
-escapeDoubleQuotes =
- gsub "\"" "''" . -- rest are right quotes .
- gsub "``\\\\footnote" "''\\\\footnote" . -- except \footnote
- gsub "\"\\\\" "``\\\\" . -- left quote before latex command
- gsub "([[:space:]])\"" "\\1``" . -- never right quote after space
- gsub "\"('|`)([^[:punct:][:space:]])" "``{}`\\2" . -- "'word left
- gsub "\"([^[:punct:][:space:]])" "``\\1" -- "word left
-
-escapeSingleQuotes =
- gsub "`\\\\footnote" "'\\\\footnote" . -- except \footnote
- gsub "'\\\\" "`\\\\" . -- left quote before latex command
- 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 "([^-])--([^-])" "\\1---\\2"
-
-escapeSmart = escapeDashes . escapeSingleQuotes . escapeDoubleQuotes .
- escapeEllipses
-
--- | Escape string for LaTeX (including smart quotes, dashes, ellipses)
+-- | Escape string for LaTeX
stringToLaTeX :: String -> String
-stringToLaTeX = escapeSmart . escapeGt . escapeLt . escapeBar . escapeHat .
+stringToLaTeX = escapeGt . escapeLt . escapeBar . escapeHat .
escapeSpecial . fixBackslash . escapeBrackets .
escapeBackslash
@@ -158,9 +131,7 @@ inlineListToLaTeX :: [Block] -- ^ List of note blocks to use in resolving note
-> [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'
+ concatMap (inlineToLaTeX notes) lst
-- | Convert inline element to LaTeX
inlineToLaTeX :: [Block] -- ^ List of note blocks to use in resolving note refs
@@ -173,6 +144,14 @@ inlineToLaTeX notes (Strong lst) = "\\textbf{" ++
inlineToLaTeX notes (Code str) = "\\verb" ++ [chr] ++ stuffing ++ [chr]
where stuffing = str
chr = ((enumFromTo '!' '~') \\ stuffing) !! 0
+inlineToLaTeX notes (Quoted SingleQuote lst) =
+ "`" ++ inlineListToLaTeX notes lst ++ "'"
+inlineToLaTeX notes (Quoted DoubleQuote lst) =
+ "``" ++ inlineListToLaTeX notes lst ++ "''"
+inlineToLaTeX notes Apostrophe = "'"
+inlineToLaTeX notes EmDash = "---"
+inlineToLaTeX notes EnDash = "--"
+inlineToLaTeX notes Ellipses = "\\ldots{}"
inlineToLaTeX notes (Str str) = stringToLaTeX str
inlineToLaTeX notes (TeX str) = str
inlineToLaTeX notes (HtmlInline str) = ""
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index d5ec137cd..343942421 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -35,6 +35,7 @@ module Text.Pandoc.Writers.Markdown (
import Text.Regex ( matchRegex, mkRegex )
import Text.Pandoc.Definition
import Text.Pandoc.Shared
+import Data.List ( group )
import Text.PrettyPrint.HughesPJ hiding ( Str )
-- | Convert Pandoc to Markdown.
@@ -154,12 +155,22 @@ 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 (Quoted SingleQuote lst) = char '\'' <>
+ (inlineListToMarkdown lst) <> char '\''
+inlineToMarkdown (Quoted DoubleQuote lst) = char '"' <>
+ (inlineListToMarkdown lst) <> char '"'
+inlineToMarkdown EmDash = text "--"
+inlineToMarkdown EnDash = char '-'
+inlineToMarkdown Apostrophe = char '\''
+inlineToMarkdown Ellipses = text "..."
+inlineToMarkdown (Code str) =
+ let tickGroups = filter (\s -> '`' `elem` s) $ group str
+ longest = if null tickGroups
+ then 0
+ else maximum $ map length tickGroups
+ marker = replicate (longest + 1) '`'
+ spacer = if (longest == 0) then "" else " " in
+ text (marker ++ spacer ++ str ++ spacer ++ marker)
inlineToMarkdown (Str str) = text $ escapeString str
inlineToMarkdown (TeX str) = text str
inlineToMarkdown (HtmlInline str) = text str
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 9184e0200..7e1581908 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -182,6 +182,14 @@ 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 (Quoted SingleQuote lst) = let (main, refs) = inlineListToRST lst in
+ (char '\'' <> main <> char '\'', refs)
+inlineToRST (Quoted DoubleQuote lst) = let (main, refs) = inlineListToRST lst in
+ (char '"' <> main <> char '"', refs)
+inlineToRST EmDash = (text "--", empty)
+inlineToRST EnDash = (char '-', empty)
+inlineToRST Apostrophe = (char '\'', empty)
+inlineToRST Ellipses = (text "...", empty)
inlineToRST (Code str) = (text $ "``" ++ str ++ "``", empty)
inlineToRST (Str str) = (text $ escapeString str, empty)
inlineToRST (TeX str) = (text str, empty)
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 28cbe2ee8..20f06d21b 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -211,6 +211,14 @@ inlineToRTF :: [Block] -- ^ list of note blocks
inlineToRTF notes (Emph lst) = "{\\i " ++ (inlineListToRTF notes lst) ++ "} "
inlineToRTF notes (Strong lst) =
"{\\b " ++ (inlineListToRTF notes lst) ++ "} "
+inlineToRTF notes (Quoted SingleQuote lst) =
+ "\\u8216'" ++ (inlineListToRTF notes lst) ++ "\\u8217'"
+inlineToRTF notes (Quoted DoubleQuote lst) =
+ "\\u8220\"" ++ (inlineListToRTF notes lst) ++ "\\u8221\""
+inlineToRTF notes Apostrophe = "\\u8217'"
+inlineToRTF notes Ellipses = "\\u8230?"
+inlineToRTF notes EmDash = "\\u8212-"
+inlineToRTF notes EnDash = "\\u8211-"
inlineToRTF notes (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "} "
inlineToRTF notes (Str str) = stringToRTF str
inlineToRTF notes (TeX str) = latexToRTF str