aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2014-04-01 09:21:23 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2014-04-01 09:21:23 -0700
commitced8be1d080019f56033c8200974598910985dc4 (patch)
tree3b52f36e9b18cdd73a09af95f4377f4f25bcadf4
parent99f4f636df36d84a4bc58f67337af3584595f5c1 (diff)
parent90269cb213ae6b2db31cc11199d1ce8d378bdac8 (diff)
downloadpandoc-ced8be1d080019f56033c8200974598910985dc4.tar.gz
Merge pull request #1207 from mpickering/htmlinlines
Fix #1162, #1175 and rewrite textile and HTML backend to use the builder
-rw-r--r--src/Text/Pandoc/Parsing.hs43
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs235
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs2
-rw-r--r--src/Text/Pandoc/Readers/RST.hs2
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs299
-rw-r--r--tests/html-reader.html5
-rw-r--r--tests/html-reader.native152
-rw-r--r--tests/opml-reader.native2
-rw-r--r--tests/textile-reader.native91
-rw-r--r--tests/textile-reader.textile6
10 files changed, 446 insertions, 391 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 68d4605ee..a9009eaa2 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -997,17 +997,17 @@ registerHeader (ident,classes,kvs) header' = do
failUnlessSmart :: HasReaderOptions st => Parser s st ()
failUnlessSmart = getOption readerSmart >>= guard
-smartPunctuation :: Parser [Char] ParserState Inline
- -> Parser [Char] ParserState Inline
+smartPunctuation :: Parser [Char] ParserState Inlines
+ -> Parser [Char] ParserState Inlines
smartPunctuation inlineParser = do
failUnlessSmart
choice [ quoted inlineParser, apostrophe, dash, ellipses ]
-apostrophe :: Parser [Char] ParserState Inline
-apostrophe = (char '\'' <|> char '\8217') >> return (Str "\x2019")
+apostrophe :: Parser [Char] ParserState Inlines
+apostrophe = (char '\'' <|> char '\8217') >> return (B.str "\x2019")
-quoted :: Parser [Char] ParserState Inline
- -> Parser [Char] ParserState Inline
+quoted :: Parser [Char] ParserState Inlines
+ -> Parser [Char] ParserState Inlines
quoted inlineParser = doubleQuoted inlineParser <|> singleQuoted inlineParser
withQuoteContext :: QuoteContext
@@ -1022,20 +1022,19 @@ withQuoteContext context parser = do
setState newState { stateQuoteContext = oldQuoteContext }
return result
-singleQuoted :: Parser [Char] ParserState Inline
- -> Parser [Char] ParserState Inline
+singleQuoted :: Parser [Char] ParserState Inlines
+ -> Parser [Char] ParserState Inlines
singleQuoted inlineParser = try $ do
singleQuoteStart
withQuoteContext InSingleQuote $ many1Till inlineParser singleQuoteEnd >>=
- return . Quoted SingleQuote . normalizeSpaces
+ return . B.singleQuoted . mconcat
-doubleQuoted :: Parser [Char] ParserState Inline
- -> Parser [Char] ParserState Inline
+doubleQuoted :: Parser [Char] ParserState Inlines
+ -> Parser [Char] ParserState Inlines
doubleQuoted inlineParser = try $ do
doubleQuoteStart
- withQuoteContext InDoubleQuote $ do
- contents <- manyTill inlineParser doubleQuoteEnd
- return . Quoted DoubleQuote . normalizeSpaces $ contents
+ withQuoteContext InDoubleQuote $ manyTill inlineParser doubleQuoteEnd >>=
+ return . B.doubleQuoted . mconcat
failIfInQuoteContext :: QuoteContext -> Parser [tok] ParserState ()
failIfInQuoteContext context = do
@@ -1079,17 +1078,17 @@ doubleQuoteEnd = do
charOrRef "\"\8221\148"
return ()
-ellipses :: Parser [Char] st Inline
+ellipses :: Parser [Char] st Inlines
ellipses = do
try (charOrRef "\8230\133") <|> try (string "..." >> return '…')
- return (Str "\8230")
+ return (B.str "\8230")
-dash :: Parser [Char] ParserState Inline
+dash :: Parser [Char] ParserState Inlines
dash = do
oldDashes <- getOption readerOldDashes
if oldDashes
then emDashOld <|> enDashOld
- else Str `fmap` (hyphenDash <|> emDash <|> enDash)
+ else B.str `fmap` (hyphenDash <|> emDash <|> enDash)
-- Two hyphens = en-dash, three = em-dash
hyphenDash :: Parser [Char] st String
@@ -1107,16 +1106,16 @@ enDash = do
try (charOrRef "\8212\151")
return "\8211"
-enDashOld :: Parser [Char] st Inline
+enDashOld :: Parser [Char] st Inlines
enDashOld = do
try (charOrRef "\8211\150") <|>
try (char '-' >> lookAhead (satisfy isDigit) >> return '–')
- return (Str "\8211")
+ return (B.str "\8211")
-emDashOld :: Parser [Char] st Inline
+emDashOld :: Parser [Char] st Inlines
emDashOld = do
try (charOrRef "\8212\151") <|> (try $ string "--" >> optional (char '-') >> return '-')
- return (Str "\8212")
+ return (B.str "\8212")
-- This is used to prevent exponential blowups for things like:
-- a**a*a**a*a**a*a**a*a**a*a**a*a**
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index d1e4d0024..4fab251bb 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -40,6 +40,7 @@ import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
import Text.Pandoc.Shared
import Text.Pandoc.Options
import Text.Pandoc.Parsing
@@ -48,6 +49,8 @@ import Data.List ( intercalate )
import Data.Char ( isDigit )
import Control.Monad ( liftM, guard, when, mzero )
import Control.Applicative ( (<$>), (<$), (<*) )
+import Data.Monoid
+import Data.Sequence (ViewL(..), ViewR(..), viewr, viewl)
isSpace :: Char -> Bool
isSpace ' ' = True
@@ -66,30 +69,30 @@ readHtml opts inp =
where tags = canonicalizeTags $
parseTagsOptions parseOptions{ optTagPosition = True } inp
parseDoc = do
- blocks <- (fixPlains False . concat) <$> manyTill block eof
+ blocks <- (fixPlains False) . mconcat <$> manyTill block eof
meta <- stateMeta <$> getState
- return $ Pandoc meta blocks
+ return $ Pandoc meta (B.toList blocks)
type TagParser = Parser [Tag String] ParserState
-pBody :: TagParser [Block]
+pBody :: TagParser Blocks
pBody = pInTags "body" block
-pHead :: TagParser [Block]
-pHead = pInTags "head" $ pTitle <|> pMetaTag <|> ([] <$ pAnyTag)
- where pTitle = pInTags "title" inline >>= setTitle . normalizeSpaces
- setTitle t = [] <$ (updateState $ B.setMeta "title" (B.fromList t))
+pHead :: TagParser Blocks
+pHead = pInTags "head" $ pTitle <|> pMetaTag <|> (mempty <$ pAnyTag)
+ where pTitle = pInTags "title" inline >>= setTitle . trimInlines
+ setTitle t = mempty <$ (updateState $ B.setMeta "title" t)
pMetaTag = do
mt <- pSatisfy (~== TagOpen "meta" [])
let name = fromAttrib "name" mt
if null name
- then return []
+ then return mempty
else do
let content = fromAttrib "content" mt
updateState $ B.setMeta name (B.text content)
- return []
+ return mempty
-block :: TagParser [Block]
+block :: TagParser Blocks
block = choice
[ pPara
, pHeader
@@ -105,10 +108,10 @@ block = choice
, pRawHtmlBlock
]
-pList :: TagParser [Block]
+pList :: TagParser Blocks
pList = pBulletList <|> pOrderedList <|> pDefinitionList
-pBulletList :: TagParser [Block]
+pBulletList :: TagParser Blocks
pBulletList = try $ do
pSatisfy (~== TagOpen "ul" [])
let nonItem = pSatisfy (\t ->
@@ -118,9 +121,9 @@ pBulletList = try $ do
-- treat it as a list item, though it's not valid xhtml...
skipMany nonItem
items <- manyTill (pInTags "li" block >>~ skipMany nonItem) (pCloses "ul")
- return [BulletList $ map (fixPlains True) items]
+ return $ B.bulletList $ map (fixPlains True) items
-pOrderedList :: TagParser [Block]
+pOrderedList :: TagParser Blocks
pOrderedList = try $ do
TagOpen _ attribs <- pSatisfy (~== TagOpen "ol" [])
let (start, style) = (sta', sty')
@@ -146,27 +149,27 @@ pOrderedList = try $ do
-- treat it as a list item, though it's not valid xhtml...
skipMany nonItem
items <- manyTill (pInTags "li" block >>~ skipMany nonItem) (pCloses "ol")
- return [OrderedList (start, style, DefaultDelim) $ map (fixPlains True) items]
+ return $ B.orderedListWith (start, style, DefaultDelim) $ map (fixPlains True) items
-pDefinitionList :: TagParser [Block]
+pDefinitionList :: TagParser Blocks
pDefinitionList = try $ do
pSatisfy (~== TagOpen "dl" [])
items <- manyTill pDefListItem (pCloses "dl")
- return [DefinitionList items]
+ return $ B.definitionList items
-pDefListItem :: TagParser ([Inline],[[Block]])
+pDefListItem :: TagParser (Inlines, [Blocks])
pDefListItem = try $ do
let nonItem = pSatisfy (\t -> not (t ~== TagOpen "dt" []) &&
not (t ~== TagOpen "dd" []) && not (t ~== TagClose "dl"))
terms <- many1 (try $ skipMany nonItem >> pInTags "dt" inline)
defs <- many1 (try $ skipMany nonItem >> pInTags "dd" block)
skipMany nonItem
- let term = intercalate [LineBreak] terms
+ let term = foldl1 (\x y -> x <> B.linebreak <> y) terms
return (term, map (fixPlains True) defs)
-fixPlains :: Bool -> [Block] -> [Block]
-fixPlains inList bs = if any isParaish bs
- then map plainToPara bs
+fixPlains :: Bool -> Blocks -> Blocks
+fixPlains inList bs = if any isParaish bs'
+ then B.fromList $ map plainToPara bs'
else bs
where isParaish (Para _) = True
isParaish (CodeBlock _ _) = True
@@ -178,6 +181,7 @@ fixPlains inList bs = if any isParaish bs
isParaish _ = False
plainToPara (Plain xs) = Para xs
plainToPara x = x
+ bs' = B.toList bs
pRawTag :: TagParser String
pRawTag = do
@@ -187,20 +191,20 @@ pRawTag = do
then return []
else return $ renderTags' [tag]
-pDiv :: TagParser [Block]
+pDiv :: TagParser Blocks
pDiv = try $ do
getOption readerParseRaw >>= guard
TagOpen _ attr <- lookAhead $ pSatisfy $ tagOpen (=="div") (const True)
contents <- pInTags "div" block
- return [Div (mkAttr attr) contents]
+ return $ B.divWith (mkAttr attr) contents
-pRawHtmlBlock :: TagParser [Block]
+pRawHtmlBlock :: TagParser Blocks
pRawHtmlBlock = do
raw <- pHtmlBlock "script" <|> pHtmlBlock "style" <|> pRawTag
parseRaw <- getOption readerParseRaw
if parseRaw && not (null raw)
- then return [RawBlock (Format "html") raw]
- else return []
+ then return $ B.rawBlock "html" raw
+ else return mempty
pHtmlBlock :: String -> TagParser String
pHtmlBlock t = try $ do
@@ -208,35 +212,34 @@ pHtmlBlock t = try $ do
contents <- manyTill pAnyTag (pSatisfy (~== TagClose t))
return $ renderTags' $ [open] ++ contents ++ [TagClose t]
-pHeader :: TagParser [Block]
+pHeader :: TagParser Blocks
pHeader = try $ do
TagOpen tagtype attr <- pSatisfy $
tagOpen (`elem` ["h1","h2","h3","h4","h5","h6"])
(const True)
let bodyTitle = TagOpen tagtype attr ~== TagOpen "h1" [("class","title")]
let level = read (drop 1 tagtype)
- contents <- liftM concat $ manyTill inline (pCloses tagtype <|> eof)
+ contents <- trimInlines . mconcat <$> manyTill inline (pCloses tagtype <|> eof)
let ident = fromMaybe "" $ lookup "id" attr
let classes = maybe [] words $ lookup "class" attr
let keyvals = [(k,v) | (k,v) <- attr, k /= "class", k /= "id"]
return $ if bodyTitle
- then [] -- skip a representation of the title in the body
- else [Header level (ident, classes, keyvals) $
- normalizeSpaces contents]
+ then mempty -- skip a representation of the title in the body
+ else B.headerWith (ident, classes, keyvals) level contents
-pHrule :: TagParser [Block]
+pHrule :: TagParser Blocks
pHrule = do
pSelfClosing (=="hr") (const True)
- return [HorizontalRule]
+ return B.horizontalRule
-pTable :: TagParser [Block]
+pTable :: TagParser Blocks
pTable = try $ do
TagOpen _ _ <- pSatisfy (~== TagOpen "table" [])
skipMany pBlank
- caption <- option [] $ pInTags "caption" inline >>~ skipMany pBlank
+ caption <- option mempty $ pInTags "caption" inline >>~ skipMany pBlank
-- TODO actually read these and take width information from them
widths' <- pColgroup <|> many pCol
- head' <- option [] $ pOptInTag "thead" $ pInTags "tr" (pCell "th")
+ head' <- option mempty $ pOptInTag "thead" $ pInTags "tr" (pCell "th")
skipMany pBlank
rows <- pOptInTag "tbody"
$ many1 $ try $ skipMany pBlank >> pInTags "tr" (pCell "td")
@@ -245,19 +248,21 @@ pTable = try $ do
let isSinglePlain [] = True
isSinglePlain [Plain _] = True
isSinglePlain _ = False
- let isSimple = all isSinglePlain $ concat (head':rows)
- let cols = length $ if null head'
- then head rows
- else head'
+ let lHead = B.toList head'
+ let lRows = map B.toList rows
+ let isSimple = all isSinglePlain (lHead:lRows)
+ let cols = length $ if null lHead
+ then head lRows
+ else lHead
-- fail if there are colspans or rowspans
- guard $ all (\r -> length r == cols) rows
+ guard $ all (\r -> length r == cols) lRows
let aligns = replicate cols AlignLeft
let widths = if null widths'
then if isSimple
then replicate cols 0
else replicate cols (1.0 / fromIntegral cols)
else widths'
- return [Table caption aligns widths head' rows]
+ return $ B.table caption (zip aligns widths) [head'] [rows]
pCol :: TagParser Double
pCol = try $ do
@@ -275,31 +280,31 @@ pColgroup = try $ do
skipMany pBlank
manyTill pCol (pCloses "colgroup" <|> eof) <* skipMany pBlank
-pCell :: String -> TagParser [TableCell]
+pCell :: String -> TagParser Blocks
pCell celltype = try $ do
skipMany pBlank
res <- pInTags celltype block
skipMany pBlank
- return [res]
+ return res
-pBlockQuote :: TagParser [Block]
+pBlockQuote :: TagParser Blocks
pBlockQuote = do
contents <- pInTags "blockquote" block
- return [BlockQuote $ fixPlains False contents]
+ return $ B.blockQuote $ fixPlains False contents
-pPlain :: TagParser [Block]
+pPlain :: TagParser Blocks
pPlain = do
- contents <- liftM (normalizeSpaces . concat) $ many1 inline
- if null contents
- then return []
- else return [Plain contents]
+ contents <- trimInlines . mconcat <$> many1 inline
+ if B.isNull contents
+ then return mempty
+ else return $ B.plain contents
-pPara :: TagParser [Block]
+pPara :: TagParser Blocks
pPara = do
- contents <- pInTags "p" inline
- return [Para $ normalizeSpaces contents]
+ contents <- trimInlines <$> pInTags "p" inline
+ return $ B.para contents
-pCodeBlock :: TagParser [Block]
+pCodeBlock :: TagParser Blocks
pCodeBlock = try $ do
TagOpen _ attr <- pSatisfy (~== TagOpen "pre" [])
contents <- manyTill pAnyTag (pCloses "pre" <|> eof)
@@ -312,9 +317,9 @@ pCodeBlock = try $ do
let result = case reverse result' of
'\n':_ -> init result'
_ -> result'
- return [CodeBlock (mkAttr attr) result]
+ return $ B.codeBlockWith (mkAttr attr) result
-inline :: TagParser [Inline]
+inline :: TagParser Inlines
inline = choice
[ pTagText
, pQ
@@ -354,7 +359,7 @@ pSelfClosing f g = do
optional $ pSatisfy (tagClose f)
return open
-pQ :: TagParser [Inline]
+pQ :: TagParser Inlines
pQ = do
quoteContext <- stateQuoteContext `fmap` getState
let quoteType = case quoteContext of
@@ -363,82 +368,93 @@ pQ = do
let innerQuoteContext = if quoteType == SingleQuote
then InSingleQuote
else InDoubleQuote
- withQuoteContext innerQuoteContext $ pInlinesInTags "q" (Quoted quoteType)
+ let constructor = case quoteType of
+ SingleQuote -> B.singleQuoted
+ DoubleQuote -> B.doubleQuoted
+ withQuoteContext innerQuoteContext $
+ pInlinesInTags "q" constructor
-pEmph :: TagParser [Inline]
-pEmph = pInlinesInTags "em" Emph <|> pInlinesInTags "i" Emph
+pEmph :: TagParser Inlines
+pEmph = pInlinesInTags "em" B.emph <|> pInlinesInTags "i" B.emph
-pStrong :: TagParser [Inline]
-pStrong = pInlinesInTags "strong" Strong <|> pInlinesInTags "b" Strong
+pStrong :: TagParser Inlines
+pStrong = pInlinesInTags "strong" B.strong <|> pInlinesInTags "b" B.strong
-pSuperscript :: TagParser [Inline]
-pSuperscript = pInlinesInTags "sup" Superscript
+pSuperscript :: TagParser Inlines
+pSuperscript = pInlinesInTags "sup" B.superscript
-pSubscript :: TagParser [Inline]
-pSubscript = pInlinesInTags "sub" Subscript
+pSubscript :: TagParser Inlines
+pSubscript = pInlinesInTags "sub" B.subscript
-pStrikeout :: TagParser [Inline]
+pStrikeout :: TagParser Inlines
pStrikeout = do
- pInlinesInTags "s" Strikeout <|>
- pInlinesInTags "strike" Strikeout <|>
- pInlinesInTags "del" Strikeout <|>
+ pInlinesInTags "s" B.strikeout <|>
+ pInlinesInTags "strike" B.strikeout <|>
+ pInlinesInTags "del" B.strikeout <|>
try (do pSatisfy (~== TagOpen "span" [("class","strikeout")])
- contents <- liftM concat $ manyTill inline (pCloses "span")
- return [Strikeout contents])
+ contents <- mconcat <$> manyTill inline (pCloses "span")
+ return $ B.strikeout contents)
-pLineBreak :: TagParser [Inline]
+pLineBreak :: TagParser Inlines
pLineBreak = do
pSelfClosing (=="br") (const True)
- return [LineBreak]
+ return B.linebreak
-pLink :: TagParser [Inline]
+pLink :: TagParser Inlines
pLink = try $ do
tag <- pSatisfy (tagOpenLit "a" (isJust . lookup "href"))
let url = fromAttrib "href" tag
let title = fromAttrib "title" tag
- lab <- liftM concat $ manyTill inline (pCloses "a")
- return [Link (normalizeSpaces lab) (escapeURI url, title)]
+ lab <- trimInlines . mconcat <$> manyTill inline (pCloses "a")
+ return $ B.link (escapeURI url) title lab
-pImage :: TagParser [Inline]
+pImage :: TagParser Inlines
pImage = do
tag <- pSelfClosing (=="img") (isJust . lookup "src")
let url = fromAttrib "src" tag
let title = fromAttrib "title" tag
let alt = fromAttrib "alt" tag
- return [Image (B.toList $ B.text alt) (escapeURI url, title)]
+ return $ B.image (escapeURI url) title (B.text alt)
-pCode :: TagParser [Inline]
+pCode :: TagParser Inlines
pCode = try $ do
(TagOpen open attr) <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True)
result <- manyTill pAnyTag (pCloses open)
- return [Code (mkAttr attr) $ intercalate " " $ lines $ innerText result]
+ return $ B.codeWith (mkAttr attr) $ intercalate " " $ lines $ innerText result
-pSpan :: TagParser [Inline]
+pSpan :: TagParser Inlines
pSpan = try $ do
getOption readerParseRaw >>= guard
TagOpen _ attr <- lookAhead $ pSatisfy $ tagOpen (=="span") (const True)
contents <- pInTags "span" inline
- return [Span (mkAttr attr) contents]
+ return $ B.spanWith (mkAttr attr) contents
-pRawHtmlInline :: TagParser [Inline]
+pRawHtmlInline :: TagParser Inlines
pRawHtmlInline = do
result <- pSatisfy (tagComment (const True)) <|> pSatisfy isInlineTag
parseRaw <- getOption readerParseRaw
if parseRaw
- then return [RawInline (Format "html") $ renderTags' [result]]
- else return []
+ then return $ B.rawInline "html" $ renderTags' [result]
+ else return mempty
-pInlinesInTags :: String -> ([Inline] -> Inline)
- -> TagParser [Inline]
+pInlinesInTags :: String -> (Inlines -> Inlines)
+ -> TagParser Inlines
pInlinesInTags tagtype f = do
- contents <- pInTags tagtype inline
- return [f $ normalizeSpaces contents]
-
-pInTags :: String -> TagParser [a]
- -> TagParser [a]
+ contents <- B.unMany <$> pInTags tagtype inline
+ let left = case viewl contents of
+ EmptyL -> mempty
+ (a :< _) -> padSpace a
+ let right = case viewr contents of
+ EmptyR -> mempty
+ (_ :> a) -> padSpace a
+ return (left <> f (trimInlines . B.Many $ contents) <> right)
+ where padSpace a = if a == Space then B.space else mempty
+
+pInTags :: (Monoid a) => String -> TagParser a
+ -> TagParser a
pInTags tagtype parser = try $ do
pSatisfy (~== TagOpen tagtype [])
- liftM concat $ manyTill parser (pCloses tagtype <|> eof)
+ mconcat <$> manyTill parser (pCloses tagtype <|> eof)
pOptInTag :: String -> TagParser a
-> TagParser a
@@ -461,36 +477,36 @@ pCloses tagtype = try $ do
(TagClose "dl") | tagtype == "li" -> return ()
_ -> mzero
-pTagText :: TagParser [Inline]
+pTagText :: TagParser Inlines
pTagText = try $ do
(TagText str) <- pSatisfy isTagText
st <- getState
case runParser (many pTagContents) st "text" str of
Left _ -> fail $ "Could not parse `" ++ str ++ "'"
- Right result -> return result
+ Right result -> return $ mconcat result
pBlank :: TagParser ()
pBlank = try $ do
(TagText str) <- pSatisfy isTagText
guard $ all isSpace str
-pTagContents :: Parser [Char] ParserState Inline
+pTagContents :: Parser [Char] ParserState Inlines
pTagContents =
- Math DisplayMath `fmap` mathDisplay
- <|> Math InlineMath `fmap` mathInline
+ B.displayMath <$> mathDisplay
+ <|> B.math <$> mathInline
<|> pStr
<|> pSpace
<|> smartPunctuation pTagContents
<|> pSymbol
<|> pBad
-pStr :: Parser [Char] ParserState Inline
+pStr :: Parser [Char] ParserState Inlines
pStr = do
result <- many1 $ satisfy $ \c ->
not (isSpace c) && not (isSpecial c) && not (isBad c)
pos <- getPosition
updateState $ \s -> s{ stateLastStrPos = Just pos }
- return $ Str result
+ return $ B.str result
isSpecial :: Char -> Bool
isSpecial '"' = True
@@ -504,13 +520,13 @@ isSpecial '\8220' = True
isSpecial '\8221' = True
isSpecial _ = False
-pSymbol :: Parser [Char] ParserState Inline
-pSymbol = satisfy isSpecial >>= return . Str . (:[])
+pSymbol :: Parser [Char] ParserState Inlines
+pSymbol = satisfy isSpecial >>= return . B.str . (:[])
isBad :: Char -> Bool
isBad c = c >= '\128' && c <= '\159' -- not allowed in HTML
-pBad :: Parser [Char] ParserState Inline
+pBad :: Parser [Char] ParserState Inlines
pBad = do
c <- satisfy isBad
let c' = case c of
@@ -542,10 +558,10 @@ pBad = do
'\158' -> '\382'
'\159' -> '\376'
_ -> '?'
- return $ Str [c']
+ return $ B.str [c']
-pSpace :: Parser [Char] ParserState Inline
-pSpace = many1 (satisfy isSpace) >> return Space
+pSpace :: Parser [Char] ParserState Inlines
+pSpace = many1 (satisfy isSpace) >> return B.space
--
-- Constants
@@ -679,3 +695,4 @@ mkAttr attr = (attribsId, attribsClasses, attribsKV)
attribsClasses = words $ fromMaybe "" $ lookup "class" attr
attribsKV = filter (\(k,_) -> k /= "class" && k /= "id") attr
+
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index aa0252266..57e1ca560 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1873,7 +1873,7 @@ smart :: MarkdownParser (F Inlines)
smart = do
getOption readerSmart >>= guard
doubleQuoted <|> singleQuoted <|>
- choice (map (return . B.singleton <$>) [apostrophe, dash, ellipses])
+ choice (map (return <$>) [apostrophe, dash, ellipses])
singleQuoted :: MarkdownParser (F Inlines)
singleQuoted = try $ do
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 127eae167..a574f343a 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -1140,7 +1140,7 @@ smart :: RSTParser Inlines
smart = do
getOption readerSmart >>= guard
doubleQuoted <|> singleQuoted <|>
- choice (map (B.singleton <$>) [apostrophe, dash, ellipses])
+ choice [apostrophe, dash, ellipses]
singleQuoted :: RSTParser Inlines
singleQuoted = try $ do
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 93658cdea..c6f992275 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -50,20 +50,20 @@ TODO : refactor common patterns across readers :
module Text.Pandoc.Readers.Textile ( readTextile) where
-
import Text.Pandoc.Definition
+import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Shared
import Text.Pandoc.Options
-import Text.Pandoc.Parsing
+import Text.Pandoc.Parsing
import Text.Pandoc.Readers.HTML ( htmlTag, isInlineTag, isBlockTag )
import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
import Text.HTML.TagSoup (parseTags, innerText, fromAttrib, Tag(..))
import Text.HTML.TagSoup.Match
import Data.List ( intercalate )
-import Data.Char ( digitToInt, isUpper )
+import Data.Char ( digitToInt, isUpper)
import Control.Monad ( guard, liftM )
import Control.Applicative ((<$>), (*>), (<*))
+import Data.Monoid
-- | Parse a Textile text and return a Pandoc document.
readTextile :: ReaderOptions -- ^ Reader options
@@ -95,7 +95,7 @@ parseTextile = do
updateState $ \s -> s { stateNotes = reverse reversedNotes }
-- now parse it for real...
blocks <- parseBlocks
- return $ Pandoc nullMeta blocks -- FIXME
+ return $ Pandoc nullMeta (B.toList blocks) -- FIXME
noteMarker :: Parser [Char] ParserState [Char]
noteMarker = skipMany spaceChar >> string "fn" >> manyTill digit (char '.')
@@ -115,11 +115,11 @@ noteBlock = try $ do
return $ replicate (sourceLine endPos - sourceLine startPos) '\n'
-- | Parse document blocks
-parseBlocks :: Parser [Char] ParserState [Block]
-parseBlocks = manyTill block eof
+parseBlocks :: Parser [Char] ParserState Blocks
+parseBlocks = mconcat <$> manyTill block eof
-- | Block parsers list tried in definition order
-blockParsers :: [Parser [Char] ParserState Block]
+blockParsers :: [Parser [Char] ParserState Blocks]
blockParsers = [ codeBlock
, header
, blockQuote
@@ -130,29 +130,32 @@ blockParsers = [ codeBlock
, rawLaTeXBlock'
, maybeExplicitBlock "table" table
, maybeExplicitBlock "p" para
+ , endBlock
]
+endBlock :: Parser [Char] ParserState Blocks
+endBlock = string "\n\n" >> return mempty
-- | Any block in the order of definition of blockParsers
-block :: Parser [Char] ParserState Block
+block :: Parser [Char] ParserState Blocks
block = choice blockParsers <?> "block"
-commentBlock :: Parser [Char] ParserState Block
+commentBlock :: Parser [Char] ParserState Blocks
commentBlock = try $ do
string "###."
manyTill anyLine blanklines
- return Null
+ return mempty
-codeBlock :: Parser [Char] ParserState Block
+codeBlock :: Parser [Char] ParserState Blocks
codeBlock = codeBlockBc <|> codeBlockPre
-codeBlockBc :: Parser [Char] ParserState Block
+codeBlockBc :: Parser [Char] ParserState Blocks
codeBlockBc = try $ do
string "bc. "
contents <- manyTill anyLine blanklines
- return $ CodeBlock ("",[],[]) $ unlines contents
+ return $ B.codeBlock (unlines contents)
-- | Code Blocks in Textile are between <pre> and </pre>
-codeBlockPre :: Parser [Char] ParserState Block
+codeBlockPre :: Parser [Char] ParserState Blocks
codeBlockPre = try $ do
(t@(TagOpen _ attrs),_) <- htmlTag (tagOpen (=="pre") (const True))
result' <- (innerText . parseTags) `fmap` -- remove internal tags
@@ -169,29 +172,29 @@ codeBlockPre = try $ do
let classes = words $ fromAttrib "class" t
let ident = fromAttrib "id" t
let kvs = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
- return $ CodeBlock (ident,classes,kvs) result'''
+ return $ B.codeBlockWith (ident,classes,kvs) result'''
-- | Header of the form "hN. content" with N in 1..6
-header :: Parser [Char] ParserState Block
+header :: Parser [Char] ParserState Blocks
header = try $ do
char 'h'
level <- digitToInt <$> oneOf "123456"
attr <- attributes
char '.'
- whitespace
- name <- normalizeSpaces <$> manyTill inline blockBreak
- attr' <- registerHeader attr (B.fromList name)
- return $ Header level attr' name
+ lookAhead whitespace
+ name <- trimInlines . mconcat <$> manyTill inline blockBreak
+ attr' <- registerHeader attr name
+ return $ B.headerWith attr' level name
-- | Blockquote of the form "bq. content"
-blockQuote :: Parser [Char] ParserState Block
+blockQuote :: Parser [Char] ParserState Blocks
blockQuote = try $ do
string "bq" >> attributes >> char '.' >> whitespace
- BlockQuote . singleton <$> para
+ B.blockQuote <$> para
-- Horizontal rule
-hrule :: Parser [Char] st Block
+hrule :: Parser [Char] st Blocks
hrule = try $ do
skipSpaces
start <- oneOf "-*"
@@ -199,62 +202,62 @@ hrule = try $ do
skipMany (spaceChar <|> char start)
newline
optional blanklines
- return HorizontalRule
+ return B.horizontalRule
-- Lists handling
-- | Can be a bullet list or an ordered list. This implementation is
-- strict in the nesting, sublist must start at exactly "parent depth
-- plus one"
-anyList :: Parser [Char] ParserState Block
+anyList :: Parser [Char] ParserState Blocks
anyList = try $ anyListAtDepth 1 <* blanklines
-- | This allow one type of list to be nested into an other type,
-- provided correct nesting
-anyListAtDepth :: Int -> Parser [Char] ParserState Block
+anyListAtDepth :: Int -> Parser [Char] ParserState Blocks
anyListAtDepth depth = choice [ bulletListAtDepth depth,
orderedListAtDepth depth,
definitionList ]
-- | Bullet List of given depth, depth being the number of leading '*'
-bulletListAtDepth :: Int -> Parser [Char] ParserState Block
-bulletListAtDepth depth = try $ BulletList <$> many1 (bulletListItemAtDepth depth)
+bulletListAtDepth :: Int -> Parser [Char] ParserState Blocks
+bulletListAtDepth depth = try $ B.bulletList <$> many1 (bulletListItemAtDepth depth)
-- | Bullet List Item of given depth, depth being the number of
-- leading '*'
-bulletListItemAtDepth :: Int -> Parser [Char] ParserState [Block]
+bulletListItemAtDepth :: Int -> Parser [Char] ParserState Blocks
bulletListItemAtDepth = genericListItemAtDepth '*'
-- | Ordered List of given depth, depth being the number of
-- leading '#'
-orderedListAtDepth :: Int -> Parser [Char] ParserState Block
+orderedListAtDepth :: Int -> Parser [Char] ParserState Blocks
orderedListAtDepth depth = try $ do
items <- many1 (orderedListItemAtDepth depth)
- return (OrderedList (1, DefaultStyle, DefaultDelim) items)
+ return $ B.orderedList items
-- | Ordered List Item of given depth, depth being the number of
-- leading '#'
-orderedListItemAtDepth :: Int -> Parser [Char] ParserState [Block]
+orderedListItemAtDepth :: Int -> Parser [Char] ParserState Blocks
orderedListItemAtDepth = genericListItemAtDepth '#'
-- | Common implementation of list items
-genericListItemAtDepth :: Char -> Int -> Parser [Char] ParserState [Block]
+genericListItemAtDepth :: Char -> Int -> Parser [Char] ParserState Blocks
genericListItemAtDepth c depth = try $ do
count depth (char c) >> attributes >> whitespace
- p <- many listInline
+ p <- mconcat <$> many listInline
newline
- sublist <- option [] (singleton <$> anyListAtDepth (depth + 1))
- return (Plain p : sublist)
+ sublist <- option mempty (anyListAtDepth (depth + 1))
+ return $ (B.plain p) <> sublist
-- | A definition list is a set of consecutive definition items
-definitionList :: Parser [Char] ParserState Block
-definitionList = try $ DefinitionList <$> many1 definitionListItem
+definitionList :: Parser [Char] ParserState Blocks
+definitionList = try $ B.definitionList <$> many1 definitionListItem
-- | List start character.
listStart :: Parser [Char] st Char
listStart = oneOf "*#-"
-listInline :: Parser [Char] ParserState Inline
+listInline :: Parser [Char] ParserState Inlines
listInline = try (notFollowedBy newline >> inline)
<|> try (endline <* notFollowedBy listStart)
@@ -262,16 +265,16 @@ listInline = try (notFollowedBy newline >> inline)
-- the term defined, then spaces and ":=". The definition follows, on
-- the same single line, or spaned on multiple line, after a line
-- break.
-definitionListItem :: Parser [Char] ParserState ([Inline], [[Block]])
+definitionListItem :: Parser [Char] ParserState (Inlines, [Blocks])
definitionListItem = try $ do
string "- "
- term <- many1Till inline (try (whitespace >> string ":="))
+ term <- mconcat <$> many1Till inline (try (whitespace >> string ":="))
def' <- multilineDef <|> inlineDef
return (term, def')
- where inlineDef :: Parser [Char] ParserState [[Block]]
- inlineDef = liftM (\d -> [[Plain d]])
- $ optional whitespace >> many listInline <* newline
- multilineDef :: Parser [Char] ParserState [[Block]]
+ where inlineDef :: Parser [Char] ParserState [Blocks]
+ inlineDef = liftM (\d -> [B.plain d])
+ $ optional whitespace >> (trimInlines . mconcat <$> many listInline) <* newline
+ multilineDef :: Parser [Char] ParserState [Blocks]
multilineDef = try $ do
optional whitespace >> newline
s <- many1Till anyChar (try (string "=:" >> newline))
@@ -288,59 +291,57 @@ blockBreak = try (newline >> blanklines >> return ()) <|>
-- raw content
-- | A raw Html Block, optionally followed by blanklines
-rawHtmlBlock :: Parser [Char] ParserState Block
+rawHtmlBlock :: Parser [Char] ParserState Blocks
rawHtmlBlock = try $ do
(_,b) <- htmlTag isBlockTag
optional blanklines
- return $ RawBlock (Format "html") b
+ return $ B.rawBlock "html" b
-- | Raw block of LaTeX content
-rawLaTeXBlock' :: Parser [Char] ParserState Block
+rawLaTeXBlock' :: Parser [Char] ParserState Blocks
rawLaTeXBlock' = do
guardEnabled Ext_raw_tex
- RawBlock (Format "latex") <$> (rawLaTeXBlock <* spaces)
+ B.rawBlock "latex" <$> (rawLaTeXBlock <* spaces)
-- | In textile, paragraphs are separated by blank lines.
-para :: Parser [Char] ParserState Block
-para = try $ Para . normalizeSpaces <$> manyTill inline blockBreak
-
+para :: Parser [Char] ParserState Blocks
+para = B.para . trimInlines . mconcat <$> manyTill inline blockBreak
-- Tables
-- | A table cell spans until a pipe |
-tableCell :: Parser [Char] ParserState TableCell
+tableCell :: Parser [Char] ParserState Blocks
tableCell = do
c <- many1 (noneOf "|\n")
- content <- parseFromString (many1 inline) c
- return $ [ Plain $ normalizeSpaces content ]
+ content <- trimInlines . mconcat <$> parseFromString (many1 inline) c
+ return $ B.plain content
-- | A table row is made of many table cells
-tableRow :: Parser [Char] ParserState [TableCell]
+tableRow :: Parser [Char] ParserState [Blocks]
tableRow = try $ ( char '|' *>
(endBy1 tableCell (optional blankline *> char '|')) <* newline)
-- | Many table rows
-tableRows :: Parser [Char] ParserState [[TableCell]]
+tableRows :: Parser [Char] ParserState [[Blocks]]
tableRows = many1 tableRow
-- | Table headers are made of cells separated by a tag "|_."
-tableHeaders :: Parser [Char] ParserState [TableCell]
+tableHeaders :: Parser [Char] ParserState [Blocks]
tableHeaders = let separator = (try $ string "|_.") in
try $ ( separator *> (sepBy1 tableCell separator) <* char '|' <* newline )
-- | A table with an optional header. Current implementation can
-- handle tables with and without header, but will parse cells
-- alignment attributes as content.
-table :: Parser [Char] ParserState Block
+table :: Parser [Char] ParserState Blocks
table = try $ do
- headers <- option [] tableHeaders
+ headers <- option mempty tableHeaders
rows <- tableRows
blanklines
let nbOfCols = max (length headers) (length $ head rows)
- return $ Table []
- (replicate nbOfCols AlignDefault)
- (replicate nbOfCols 0.0)
+ return $ B.table mempty
+ (zip (replicate nbOfCols AlignDefault) (replicate nbOfCols 0.0))
headers
rows
@@ -348,8 +349,8 @@ table = try $ do
-- | Blocks like 'p' and 'table' do not need explicit block tag.
-- However, they can be used to set HTML/CSS attributes when needed.
maybeExplicitBlock :: String -- ^ block tag name
- -> Parser [Char] ParserState Block -- ^ implicit block
- -> Parser [Char] ParserState Block
+ -> Parser [Char] ParserState Blocks -- ^ implicit block
+ -> Parser [Char] ParserState Blocks
maybeExplicitBlock name blk = try $ do
optional $ try $ string name >> attributes >> char '.' >>
optional whitespace >> optional endline
@@ -363,12 +364,14 @@ maybeExplicitBlock name blk = try $ do
-- | Any inline element
-inline :: Parser [Char] ParserState Inline
-inline = choice inlineParsers <?> "inline"
+inline :: Parser [Char] ParserState Inlines
+inline = do
+ choice inlineParsers <?> "inline"
-- | Inline parsers tried in order
-inlineParsers :: [Parser [Char] ParserState Inline]
-inlineParsers = [ str
+inlineParsers :: [Parser [Char] ParserState Inlines]
+inlineParsers = [ inlineMarkup
+ , str
, whitespace
, endline
, code
@@ -378,58 +381,57 @@ inlineParsers = [ str
, rawLaTeXInline'
, note
, try $ (char '[' *> inlineMarkup <* char ']')
- , inlineMarkup
, link
, image
, mark
- , (Str . (:[])) <$> characterReference
+ , (B.str . (:[])) <$> characterReference
, smartPunctuation inline
, symbol
]
-- | Inline markups
-inlineMarkup :: Parser [Char] ParserState Inline
-inlineMarkup = choice [ simpleInline (string "??") (Cite [])
- , simpleInline (string "**") Strong
- , simpleInline (string "__") Emph
- , simpleInline (char '*') Strong
- , simpleInline (char '_') Emph
- , simpleInline (char '+') Emph -- approximates underline
- , simpleInline (char '-' <* notFollowedBy (char '-')) Strikeout
- , simpleInline (char '^') Superscript
- , simpleInline (char '~') Subscript
+inlineMarkup :: Parser [Char] ParserState Inlines
+inlineMarkup = choice [ simpleInline (string "??") (B.cite [])
+ , simpleInline (string "**") B.strong
+ , simpleInline (string "__") B.emph
+ , simpleInline (char '*') B.strong
+ , simpleInline (char '_') B.emph
+ , simpleInline (char '+') B.emph -- approximates underline
+ , simpleInline (char '-' <* notFollowedBy (char '-')) B.strikeout
+ , simpleInline (char '^') B.superscript
+ , simpleInline (char '~') B.subscript
]
-- | Trademark, registered, copyright
-mark :: Parser [Char] st Inline
+mark :: Parser [Char] st Inlines
mark = try $ char '(' >> (try tm <|> try reg <|> copy)
-reg :: Parser [Char] st Inline
+reg :: Parser [Char] st Inlines
reg = do
oneOf "Rr"
char ')'
- return $ Str "\174"
+ return $ B.str "\174"
-tm :: Parser [Char] st Inline
+tm :: Parser [Char] st Inlines
tm = do
oneOf "Tt"
oneOf "Mm"
char ')'
- return $ Str "\8482"
+ return $ B.str "\8482"
-copy :: Parser [Char] st Inline
+copy :: Parser [Char] st Inlines
copy = do
oneOf "Cc"
char ')'
- return $ Str "\169"
+ return $ B.str "\169"
-note :: Parser [Char] ParserState Inline
+note :: Parser [Char] ParserState Inlines
note = try $ do
ref <- (char '[' *> many1 digit <* char ']')
notes <- stateNotes <$> getState
case lookup ref notes of
Nothing -> fail "note not found"
- Just raw -> liftM Note $ parseFromString parseBlocks raw
+ Just raw -> B.note <$> parseFromString parseBlocks raw
-- | Special chars
markupChars :: [Char]
@@ -450,7 +452,7 @@ wordBoundaries = markupChars ++ stringBreakers
hyphenedWords :: Parser [Char] ParserState String
hyphenedWords = do
x <- wordChunk
- xs <- many (try $ char '-' >> wordChunk)
+ xs <- many (try $ char '-' >> wordChunk)
return $ intercalate "-" (x:xs)
wordChunk :: Parser [Char] ParserState String
@@ -462,7 +464,7 @@ wordChunk = try $ do
return $ hd:tl
-- | Any string
-str :: Parser [Char] ParserState Inline
+str :: Parser [Char] ParserState Inlines
str = do
baseStr <- hyphenedWords
-- RedCloth compliance : if parsed word is uppercase and immediatly
@@ -472,89 +474,89 @@ str = do
acro <- enclosed (char '(') (char ')') anyChar
return $ concat [baseStr, " (", acro, ")"]
updateLastStrPos
- return $ Str fullStr
+ return $ B.str fullStr
-- | Textile allows HTML span infos, we discard them
-htmlSpan :: Parser [Char] ParserState Inline
-htmlSpan = try $ Str <$> ( char '%' *> attributes *> manyTill anyChar (char '%') )
+htmlSpan :: Parser [Char] ParserState Inlines
+htmlSpan = try $ B.str <$> ( char '%' *> attributes *> manyTill anyChar (char '%') )
-- | Some number of space chars
-whitespace :: Parser [Char] ParserState Inline
-whitespace = many1 spaceChar >> return Space <?> "whitespace"
+whitespace :: Parser [Char] ParserState Inlines
+whitespace = many1 spaceChar >> return B.space <?> "whitespace"
-- | In Textile, an isolated endline character is a line break
-endline :: Parser [Char] ParserState Inline
+endline :: Parser [Char] ParserState Inlines
endline = try $ do
newline >> notFollowedBy blankline
- return LineBreak
+ return B.linebreak
-rawHtmlInline :: Parser [Char] ParserState Inline
-rawHtmlInline = RawInline (Format "html") . snd <$> htmlTag isInlineTag
+rawHtmlInline :: Parser [Char] ParserState Inlines
+rawHtmlInline = B.rawInline "html" . snd <$> htmlTag isInlineTag
-- | Raw LaTeX Inline
-rawLaTeXInline' :: Parser [Char] ParserState Inline
+rawLaTeXInline' :: Parser [Char] ParserState Inlines
rawLaTeXInline' = try $ do
guardEnabled Ext_raw_tex
- rawLaTeXInline
+ B.singleton <$> rawLaTeXInline
-- | Textile standard link syntax is "label":target. But we
-- can also have ["label":target].
-link :: Parser [Char] ParserState Inline
+link :: Parser [Char] ParserState Inlines
link = linkB <|> linkNoB
-linkNoB :: Parser [Char] ParserState Inline
+linkNoB :: Parser [Char] ParserState Inlines
linkNoB = try $ do
- name <- surrounded (char '"') inline
+ name <- mconcat <$> surrounded (char '"') (withQuoteContext InDoubleQuote inline)
char ':'
let stopChars = "!.,;:"
url <- manyTill nonspaceChar (lookAhead $ space <|> try (oneOf stopChars >> (space <|> newline)))
- let name' = if name == [Str "$"] then [Str url] else name
- return $ Link name' (url, "")
+ let name' = if B.toList name == [Str "$"] then B.str url else name
+ return $ B.link url "" name'
-linkB :: Parser [Char] ParserState Inline
+linkB :: Parser [Char] ParserState Inlines
linkB = try $ do
char '['
- name <- surrounded (char '"') inline
+ name <- mconcat <$> surrounded (char '"') inline
char ':'
url <- manyTill nonspaceChar (char ']')
- let name' = if name == [Str "$"] then [Str url] else name
- return $ Link name' (url, "")
+ let name' = if B.toList name == [Str "$"] then B.str url else name
+ return $ B.link url "" name'
-- | image embedding
-image :: Parser [Char] ParserState Inline
+image :: Parser [Char] ParserState Inlines
image = try $ do
char '!' >> notFollowedBy space
src <- manyTill anyChar (lookAhead $ oneOf "!(")
alt <- option "" (try $ (char '(' >> manyTill anyChar (char ')')))
char '!'
- return $ Image [Str alt] (src, alt)
+ return $ B.image src alt (B.str alt)
-escapedInline :: Parser [Char] ParserState Inline
+escapedInline :: Parser [Char] ParserState Inlines
escapedInline = escapedEqs <|> escapedTag
-escapedEqs :: Parser [Char] ParserState Inline
-escapedEqs = Str <$> (try $ string "==" *> manyTill anyChar (try $ string "=="))
+escapedEqs :: Parser [Char] ParserState Inlines
+escapedEqs = B.str <$> (try $ string "==" *> manyTill anyChar (try $ string "=="))
-- | literal text escaped btw <notextile> tags
-escapedTag :: Parser [Char] ParserState Inline
-escapedTag = Str <$>
+escapedTag :: Parser [Char] ParserState Inlines
+escapedTag = B.str <$>
(try $ string "<notextile>" *> manyTill anyChar (try $ string "</notextile>"))
-- | Any special symbol defined in wordBoundaries
-symbol :: Parser [Char] ParserState Inline
-symbol = Str . singleton <$> (oneOf wordBoundaries <|> oneOf markupChars)
+symbol :: Parser [Char] ParserState Inlines
+symbol = B.str . singleton <$> (oneOf wordBoundaries <|> oneOf markupChars)
-- | Inline code
-code :: Parser [Char] ParserState Inline
+code :: Parser [Char] ParserState Inlines
code = code1 <|> code2
-code1 :: Parser [Char] ParserState Inline
-code1 = Code nullAttr <$> surrounded (char '@') anyChar
+code1 :: Parser [Char] ParserState Inlines
+code1 = B.code <$> surrounded (char '@') anyChar
-code2 :: Parser [Char] ParserState Inline
+code2 :: Parser [Char] ParserState Inlines
code2 = do
htmlTag (tagOpen (=="tt") null)
- Code nullAttr <$> manyTill anyChar (try $ htmlTag $ tagClose (=="tt"))
+ B.code <$> manyTill anyChar (try $ htmlTag $ tagClose (=="tt"))
-- | Html / CSS attributes
attributes :: Parser [Char] ParserState Attr
@@ -581,7 +583,7 @@ styleAttr = do
langAttr :: Parser [Char] ParserState (Attr -> Attr)
langAttr = do
- lang <- try $ enclosed (char '[') (char ']') anyChar
+ lang <- try $ enclosed (char '[') (char ']') alphaNum
return $ \(id',classes,keyvals) -> (id',classes,("lang",lang):keyvals)
-- | Parses material surrounded by a parser.
@@ -590,14 +592,43 @@ surrounded :: Parser [Char] st t -- ^ surrounding parser
-> Parser [Char] st [a]
surrounded border = enclosed (border *> notFollowedBy (oneOf " \t\n\r")) (try border)
--- | Inlines are most of the time of the same form
+
simpleInline :: Parser [Char] ParserState t -- ^ surrounding parser
- -> ([Inline] -> Inline) -- ^ Inline constructor
- -> Parser [Char] ParserState Inline -- ^ content parser (to be used repeatedly)
-simpleInline border construct = surrounded border inlineWithAttribute >>=
- return . construct . normalizeSpaces
- where inlineWithAttribute = (try $ optional attributes) >> inline
+ -> (Inlines -> Inlines) -- ^ Inline constructor
+ -> Parser [Char] ParserState Inlines -- ^ content parser (to be used repeatedly)
+simpleInline border construct = groupedSimpleInline border construct <|> ungroupedSimpleInline border construct
+
+ungroupedSimpleInline :: Parser [Char] ParserState t -- ^ surrounding parser
+ -> (Inlines -> Inlines) -- ^ Inline constructor
+ -> Parser [Char] ParserState Inlines -- ^ content parser (to be used repeatedly)
+ungroupedSimpleInline border construct = try $ do
+ st <- getState
+ pos <- getPosition
+ isWhitespace <- option False (whitespace >> return True)
+ guard $ (stateQuoteContext st /= NoQuote)
+ || (sourceColumn pos == 1)
+ || isWhitespace
+ body <- surrounded border inlineWithAttribute
+ lookAhead (notFollowedBy alphaNum)
+ let result = construct $ mconcat body
+ return $ if isWhitespace then B.space <> result
+ else result
+ where
+ inlineWithAttribute = (try $ optional attributes) >> notFollowedBy (string "\n\n")
+ >> (withQuoteContext InSingleQuote inline)
+
+
+groupedSimpleInline :: Parser [Char] ParserState t
+ -> (Inlines -> Inlines)
+ -> Parser [Char] ParserState Inlines
+groupedSimpleInline border construct = try $ do
+ char '['
+ withQuoteContext InSingleQuote (simpleInline border construct) >>~ char ']'
+
+
+
-- | Create a singleton list
singleton :: a -> [a]
singleton x = [x]
+
diff --git a/tests/html-reader.html b/tests/html-reader.html
index 69bb9ba8a..b7e5c0d2f 100644
--- a/tests/html-reader.html
+++ b/tests/html-reader.html
@@ -426,5 +426,10 @@ An e-mail address: nobody [at] nowhere.net<blockquote>
<pre><code> { &lt;code> }
</code></pre>
<p>If you want, you can use a caret at the beginning of every line, as with blockquotes, but all that you need is a caret at the beginning of the first line of the block and any preceding blank lines.</p>
+<p>text<em> Leading space</em></p>
+<p><em>Trailing space </em>text</p>
+<p>text<em> Leading spaces</em></p>
+<p><em>Trailing spaces </em>text</p>
+
</body>
</html>
diff --git a/tests/html-reader.native b/tests/html-reader.native
index e80905729..a6a3ab177 100644
--- a/tests/html-reader.native
+++ b/tests/html-reader.native
@@ -1,5 +1,5 @@
Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
-[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Str ".",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber",Str "'",Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
+[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Headers"]
,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")]
@@ -14,15 +14,15 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,Para [Str "with",Space,Str "no",Space,Str "blank",Space,Str "line"]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Paragraphs"]
-,Para [Str "Here",Str "'",Str "s",Space,Str "a",Space,Str "regular",Space,Str "paragraph",Str "."]
-,Para [Str "In",Space,Str "Markdown",Space,Str "1",Str ".",Str "0",Str ".",Str "0",Space,Str "and",Space,Str "earlier",Str ".",Space,Str "Version",Space,Str "8",Str ".",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item",Str ".",Space,Str "Because",Space,Str "a",Space,Str "hard",Str "-",Str "wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item",Str "."]
-,Para [Str "Here",Str "'",Str "s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet",Str ".",Space,Str "*",Space,Str "criminey",Str "."]
-,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "hard",Space,Str "line",Space,Str "break",LineBreak,Space,Str "here",Str "."]
+,Para [Str "Here's",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
+,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",Space,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
+,Para [Str "Here's",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
+,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "hard",Space,Str "line",Space,Str "break",LineBreak,Space,Str "here."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Block",Space,Str "Quotes"]
-,Para [Str "E",Str "-",Str "mail",Space,Str "style:"]
+,Para [Str "E-mail",Space,Str "style:"]
,BlockQuote
- [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short",Str "."]]
+ [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
,BlockQuote
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
@@ -35,8 +35,8 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
[Para [Str "nested"]]
,BlockQuote
[Para [Str "nested"]]]
-,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1",Str "."]
-,Para [Str "Box",Str "-",Str "style:"]
+,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1."]
+,Para [Str "Box-style:"]
,BlockQuote
[Para [Str "Example:"]
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"]
@@ -44,12 +44,12 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
[OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "do",Space,Str "laundry"]]
,[Plain [Str "take",Space,Str "out",Space,Str "the",Space,Str "trash"]]]]
-,Para [Str "Here",Str "'",Str "s",Space,Str "a",Space,Str "nested",Space,Str "one:"]
+,Para [Str "Here's",Space,Str "a",Space,Str "nested",Space,Str "one:"]
,BlockQuote
[Para [Str "Joe",Space,Str "said:"]
,BlockQuote
- [Para [Str "Don",Str "'",Str "t",Space,Str "quote",Space,Str "me",Str "."]]]
-,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph",Str "."]
+ [Para [Str "Don't",Space,Str "quote",Space,Str "me."]]]
+,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Code",Space,Str "Blocks"]
,Para [Str "Code:"]
@@ -112,10 +112,10 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,[Para [Str "Three"]]]
,Para [Str "Multiple",Space,Str "paragraphs:"]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one",Str "."]
- ,Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Str "'",Str "s",Space,Str "back",Str "."]]
- ,[Para [Str "Item",Space,Str "2",Str "."]]
- ,[Para [Str "Item",Space,Str "3",Str "."]]]
+ [[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one."]
+ ,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog's",Space,Str "back."]]
+ ,[Para [Str "Item",Space,Str "2."]]
+ ,[Para [Str "Item",Space,Str "3."]]]
,Header 2 ("",[],[]) [Str "Nested"]
,BulletList
[[Plain [Str "Tab"]
@@ -123,7 +123,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
[[Plain [Str "Tab"]
,BulletList
[[Plain [Str "Tab"]]]]]]]
-,Para [Str "Here",Str "'",Str "s",Space,Str "another:"]
+,Para [Str "Here's",Space,Str "another:"]
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "First"]]
,[Plain [Str "Second:"]
@@ -163,63 +163,63 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,OrderedList (1,UpperAlpha,DefaultDelim)
[[Plain [Str "Upper",Space,Str "Alpha"]
,OrderedList (1,UpperRoman,DefaultDelim)
- [[Plain [Str "Upper",Space,Str "Roman",Str "."]
+ [[Plain [Str "Upper",Space,Str "Roman."]
,OrderedList (6,Decimal,DefaultDelim)
[[Plain [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
,OrderedList (3,LowerAlpha,DefaultDelim)
[[Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
,Para [Str "Autonumbering:"]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Plain [Str "Autonumber",Str "."]]
- ,[Plain [Str "More",Str "."]
+ [[Plain [Str "Autonumber."]]
+ ,[Plain [Str "More."]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Plain [Str "Nested",Str "."]]]]]
+ [[Plain [Str "Nested."]]]]]
,HorizontalRule
,Header 2 ("",[],[]) [Str "Definition"]
,DefinitionList
[([Str "Violin"],
- [[Plain [Str "Stringed",Space,Str "musical",Space,Str "instrument",Str "."]]
- ,[Plain [Str "Torture",Space,Str "device",Str "."]]])
+ [[Plain [Str "Stringed",Space,Str "musical",Space,Str "instrument."]]
+ ,[Plain [Str "Torture",Space,Str "device."]]])
,([Str "Cello",LineBreak,Str "Violoncello"],
- [[Plain [Str "Low",Str "-",Str "voiced",Space,Str "stringed",Space,Str "instrument",Str "."]]])]
+ [[Plain [Str "Low-voiced",Space,Str "stringed",Space,Str "instrument."]]])]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
-,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]]]
-,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
-,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]]]
-,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
+,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
+,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
+,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
+,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
-,Para [Str "\"",Str "Hello,",Str "\"",Space,Str "said",Space,Str "the",Space,Str "spider",Str ".",Space,Str "\"",Str "'",Str "Shelob",Str "'",Space,Str "is",Space,Str "my",Space,Str "name",Str ".",Str "\""]
-,Para [Str "'",Str "A",Str "'",Str ",",Space,Str "'",Str "B",Str "'",Str ",",Space,Str "and",Space,Str "'",Str "C",Str "'",Space,Str "are",Space,Str "letters",Str "."]
-,Para [Str "'",Str "Oak,",Str "'",Space,Str "'",Str "elm,",Str "'",Space,Str "and",Space,Str "'",Str "beech",Str "'",Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees",Str ".",Space,Str "So",Space,Str "is",Space,Str "'",Str "pine",Str ".",Str "'"]
-,Para [Str "'",Str "He",Space,Str "said,",Space,Str "\"",Str "I",Space,Str "want",Space,Str "to",Space,Str "go",Str ".",Str "\"",Str "'",Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70",Str "'",Str "s?"]
-,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code ("",[],[]) "code",Str "'",Space,Str "and",Space,Str "a",Space,Str "\"",Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"",Str "."]
-,Para [Str "Some",Space,Str "dashes:",Space,Str "one",Str "-",Str "-",Str "-",Str "two",Space,Str "-",Str "-",Str "-",Space,Str "three",Str "-",Str "-",Str "four",Space,Str "-",Str "-",Space,Str "five",Str "."]
-,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5",Str "-",Str "7,",Space,Str "255",Str "-",Str "66,",Space,Str "1987",Str "-",Str "1999",Str "."]
-,Para [Str "Ellipses",Str ".",Str ".",Str ".",Str "and",Str ".",Space,Str ".",Space,Str ".",Str "and",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "."]
+,Para [Str "\"Hello,\"",Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Str "\"'Shelob'",Space,Str "is",Space,Str "my",Space,Str "name.\""]
+,Para [Str "'A',",Space,Str "'B',",Space,Str "and",Space,Str "'C'",Space,Str "are",Space,Str "letters."]
+,Para [Str "'Oak,'",Space,Str "'elm,'",Space,Str "and",Space,Str "'beech'",Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Str "'pine.'"]
+,Para [Str "'He",Space,Str "said,",Space,Str "\"I",Space,Str "want",Space,Str "to",Space,Str "go.\"'",Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70's?"]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code ("",[],[]) "code",Str "'",Space,Str "and",Space,Str "a",Space,Str "\"",Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"."]
+,Para [Str "Some",Space,Str "dashes:",Space,Str "one---two",Space,Str "---",Space,Str "three--four",Space,Str "--",Space,Str "five."]
+,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5-7,",Space,Str "255-66,",Space,Str "1987-1999."]
+,Para [Str "Ellipses...and.",Space,Str ".",Space,Str ".and",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "LaTeX"]
,BulletList
- [[Plain [Str "\\cite[22",Str "-",Str "23]{smith",Str ".",Str "1899}"]]
+ [[Plain [Str "\\cite[22-23]{smith.1899}"]]
,[Plain [Str "\\doublespacing"]]
- ,[Plain [Str "$",Str "2+2=4",Str "$"]]
- ,[Plain [Str "$",Str "x",Space,Str "\\in",Space,Str "y",Str "$"]]
- ,[Plain [Str "$",Str "\\alpha",Space,Str "\\wedge",Space,Str "\\omega",Str "$"]]
- ,[Plain [Str "$",Str "223",Str "$"]]
- ,[Plain [Str "$",Str "p",Str "$",Str "-",Str "Tree"]]
- ,[Plain [Str "$",Str "\\frac{d}{dx}f(x)=\\lim_{h\\to",Space,Str "0}\\frac{f(x+h)",Str "-",Str "f(x)}{h}",Str "$"]]
- ,[Plain [Str "Here",Str "'",Str "s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Str "$",Str "\\alpha",Space,Str "+",Space,Str "\\omega",Space,Str "\\times",Space,Str "x^2",Str "$",Str "."]]]
-,Para [Str "These",Space,Str "shouldn",Str "'",Str "t",Space,Str "be",Space,Str "math:"]
+ ,[Plain [Str "$2+2=4$"]]
+ ,[Plain [Str "$x",Space,Str "\\in",Space,Str "y$"]]
+ ,[Plain [Str "$\\alpha",Space,Str "\\wedge",Space,Str "\\omega$"]]
+ ,[Plain [Str "$223$"]]
+ ,[Plain [Str "$p$-Tree"]]
+ ,[Plain [Str "$\\frac{d}{dx}f(x)=\\lim_{h\\to",Space,Str "0}\\frac{f(x+h)-f(x)}{h}$"]]
+ ,[Plain [Str "Here's",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Str "$\\alpha",Space,Str "+",Space,Str "\\omega",Space,Str "\\times",Space,Str "x^2$."]]]
+,Para [Str "These",Space,Str "shouldn't",Space,Str "be",Space,Str "math:"]
,BulletList
[[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
- ,[Plain [Str "$",Str "22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money",Str ".",Space,Str "So",Space,Str "is",Space,Str "$",Str "34,000",Str ".",Space,Str "(It",Space,Str "worked",Space,Str "if",Space,Str "\"",Str "lot",Str "\"",Space,Str "is",Space,Str "emphasized",Str ".",Str ")"]]
- ,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
-,Para [Str "Here",Str "'",Str "s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
+ ,[Plain [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",Space,Str "(It",Space,Str "worked",Space,Str "if",Space,Str "\"lot\"",Space,Str "is",Space,Str "emphasized.)"]]
+ ,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
+,Para [Str "Here's",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
,Para [Str "\\begin{tabular}{|l|l|}\\hline",Space,Str "Animal",Space,Str "&",Space,Str "Number",Space,Str "\\\\",Space,Str "\\hline",Space,Str "Dog",Space,Str "&",Space,Str "2",Space,Str "\\\\",Space,Str "Cat",Space,Str "&",Space,Str "1",Space,Str "\\\\",Space,Str "\\hline",Space,Str "\\end{tabular}"]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Special",Space,Str "Characters"]
@@ -230,11 +230,11 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,[Plain [Str "section:",Space,Str "\167"]]
,[Plain [Str "set",Space,Str "membership:",Space,Str "\8712"]]
,[Plain [Str "copyright:",Space,Str "\169"]]]
-,Para [Str "AT&T",Space,Str "has",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "their",Space,Str "name",Str "."]
-,Para [Str "AT&T",Space,Str "is",Space,Str "another",Space,Str "way",Space,Str "to",Space,Str "write",Space,Str "it",Str "."]
-,Para [Str "This",Space,Str "&",Space,Str "that",Str "."]
-,Para [Str "4",Space,Str "<",Space,Str "5",Str "."]
-,Para [Str "6",Space,Str ">",Space,Str "5",Str "."]
+,Para [Str "AT&T",Space,Str "has",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "their",Space,Str "name."]
+,Para [Str "AT&T",Space,Str "is",Space,Str "another",Space,Str "way",Space,Str "to",Space,Str "write",Space,Str "it."]
+,Para [Str "This",Space,Str "&",Space,Str "that."]
+,Para [Str "4",Space,Str "<",Space,Str "5."]
+,Para [Str "6",Space,Str ">",Space,Str "5."]
,Para [Str "Backslash:",Space,Str "\\"]
,Para [Str "Backtick:",Space,Str "`"]
,Para [Str "Asterisk:",Space,Str "*"]
@@ -245,7 +245,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,Para [Str "Right",Space,Str "bracket:",Space,Str "]"]
,Para [Str "Left",Space,Str "paren:",Space,Str "("]
,Para [Str "Right",Space,Str "paren:",Space,Str ")"]
-,Para [Str "Greater",Str "-",Str "than:",Space,Str ">"]
+,Para [Str "Greater-than:",Space,Str ">"]
,Para [Str "Hash:",Space,Str "#"]
,Para [Str "Period:",Space,Str "."]
,Para [Str "Bang:",Space,Str "!"]
@@ -260,47 +260,51 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")]
-,Para [Str "Email",Space,Str "link",Space,Str "(nobody",Space,Str "[at]",Space,Str "nowhere",Str ".",Str "net)"]
+,Para [Str "Email",Space,Str "link",Space,Str "(nobody",Space,Str "[at]",Space,Str "nowhere.net)"]
,Para [Link [Str "Empty"] ("",""),Str "."]
,Header 2 ("",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
-,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link",Str "."]
+,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "thrice"] ("/url",""),Str "."]
-,Para [Str "This",Space,Str "should",Space,Str "[not]",Space,Str "be",Space,Str "a",Space,Str "link",Str "."]
+,Para [Str "This",Space,Str "should",Space,Str "[not]",Space,Str "be",Space,Str "a",Space,Str "link."]
,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."]
,Header 2 ("",[],[]) [Str "With",Space,Str "ampersands"]
-,Para [Str "Here",Str "'",Str "s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
-,Para [Str "Here",Str "'",Str "s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/","AT&T"),Str "."]
-,Para [Str "Here",Str "'",Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
-,Para [Str "Here",Str "'",Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
+,Para [Str "Here's",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
+,Para [Str "Here's",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/","AT&T"),Str "."]
+,Para [Str "Here's",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
+,Para [Str "Here's",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 ("",[],[]) [Str "Autolinks"]
-,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example",Str ".",Str "com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list?"]]
- ,[Plain [Link [Str "http://example",Str ".",Str "com/"] ("http://example.com/","")]]
- ,[Plain [Str "It",Space,Str "should",Str "."]]]
-,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere",Str ".",Str "net"]
+ ,[Plain [Link [Str "http://example.com/"] ("http://example.com/","")]]
+ ,[Plain [Str "It",Space,Str "should."]]]
+,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere.net"]
,BlockQuote
- [Para [Str "Blockquoted:",Space,Link [Str "http://example",Str ".",Str "com/"] ("http://example.com/","")]]
-,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
+ [Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]]
+,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule
,Header 1 ("",[],[]) [Str "Images"]
-,Para [Str "From",Space,Str "\"",Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune",Str "\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
+,Para [Str "From",Space,Str "\"Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "lalune"] ("lalune.jpg","Voyage dans la Lune")]
-,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon",Str "."]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Footnotes"]
-,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Link [Str "(1)"] ("#note_1",""),Str ",",Space,Str "and",Space,Str "another",Link [Str "(longnote)"] ("#note_longnote",""),Str ".",Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space^(my",Space,Str "note)",Str "."]
-,Para [Link [Str "(1)"] ("#ref_1",""),Space,Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end",Str "."]
-,Para [Link [Str "(longnote)"] ("#ref_longnote",""),Space,Str "Here",Str "'",Str "s",Space,Str "the",Space,Str "other",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."]
-,Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",Space,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)",Str "."]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Link [Str "(1)"] ("#note_1",""),Str ",",Space,Str "and",Space,Str "another",Link [Str "(longnote)"] ("#note_longnote",""),Str ".",Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space^(my",Space,Str "note)."]
+,Para [Link [Str "(1)"] ("#ref_1",""),Space,Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end."]
+,Para [Link [Str "(longnote)"] ("#ref_longnote",""),Space,Str "Here's",Space,Str "the",Space,Str "other",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."]
+,Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",Space,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)."]
,CodeBlock ("",[],[]) " { <code> }"
-,Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",Space,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines",Str "."]]
+,Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",Space,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines."]
+,Para [Str "text",Space,Emph [Str "Leading",Space,Str "space"]]
+,Para [Emph [Str "Trailing",Space,Str "space"],Space,Str "text"]
+,Para [Str "text",Space,Emph [Str "Leading",Space,Str "spaces"]]
+,Para [Emph [Str "Trailing",Space,Str "spaces"],Space,Str "text"]]
diff --git a/tests/opml-reader.native b/tests/opml-reader.native
index e71857680..14aff2c03 100644
--- a/tests/opml-reader.native
+++ b/tests/opml-reader.native
@@ -19,7 +19,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Dave",Spa
,Header 3 ("",[],[]) [Str "North",Space,Str "Dakota"]
,Header 3 ("",[],[]) [Str "Oklahoma"]
,Header 3 ("",[],[]) [Str "South",Space,Str "Dakota"]
-,Header 2 ("",[],[]) [Str "Mid",Str "-",Str "Atlantic"]
+,Header 2 ("",[],[]) [Str "Mid-Atlantic"]
,Header 3 ("",[],[]) [Str "Delaware"]
,Header 3 ("",[],[]) [Str "Maryland"]
,Header 3 ("",[],[]) [Str "New",Space,Str "Jersey"]
diff --git a/tests/textile-reader.native b/tests/textile-reader.native
index ebfbc07fd..0c2b13e72 100644
--- a/tests/textile-reader.native
+++ b/tests/textile-reader.native
@@ -1,5 +1,5 @@
Pandoc (Meta {unMeta = fromList []})
-[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader",Str ".",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber",Str "\8217",Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
+[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader.",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embeded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embeded",Space,Str "link"] ("http://www.example.com","")]
@@ -8,42 +8,42 @@ Pandoc (Meta {unMeta = fromList []})
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
,Header 6 ("level-6",[],[]) [Str "Level",Space,Str "6"]
,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"]
-,Para [Str "Here",Str "\8217",Str "s",Space,Str "a",Space,Str "regular",Space,Str "paragraph",Str "."]
-,Para [Str "Line",Space,Str "breaks",Space,Str "are",Space,Str "preserved",Space,Str "in",Space,Str "textile",Str ",",Space,Str "so",Space,Str "you",Space,Str "can",Space,Str "not",Space,Str "wrap",Space,Str "your",Space,Str "very",LineBreak,Str "long",Space,Str "paragraph",Space,Str "with",Space,Str "your",Space,Str "favourite",Space,Str "text",Space,Str "editor",Space,Str "and",Space,Str "have",Space,Str "it",Space,Str "rendered",LineBreak,Str "with",Space,Str "no",Space,Str "break",Str "."]
-,Para [Str "Here",Str "\8217",Str "s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet",Str "."]
+,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
+,Para [Str "Line",Space,Str "breaks",Space,Str "are",Space,Str "preserved",Space,Str "in",Space,Str "textile,",Space,Str "so",Space,Str "you",Space,Str "can",Space,Str "not",Space,Str "wrap",Space,Str "your",Space,Str "very",LineBreak,Str "long",Space,Str "paragraph",Space,Str "with",Space,Str "your",Space,Str "favourite",Space,Str "text",Space,Str "editor",Space,Str "and",Space,Str "have",Space,Str "it",Space,Str "rendered",LineBreak,Str "with",Space,Str "no",Space,Str "break."]
+,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet."]
,BulletList
- [[Plain [Str "criminey",Str "."]]]
+ [[Plain [Str "criminey."]]]
,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "paragraph",Space,Str "break",Space,Str "between",Space,Str "here"]
-,Para [Str "and",Space,Str "here",Str "."]
-,Para [Str "pandoc",Space,Str "converts",Space,Str "textile",Str "."]
+,Para [Str "and",Space,Str "here."]
+,Para [Str "pandoc",Space,Str "converts",Space,Str "textile."]
,Header 1 ("block-quotes",[],[]) [Str "Block",Space,Str "Quotes"]
,BlockQuote
- [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "famous",Space,Str "quote",Space,Str "from",Space,Str "somebody",Str ".",Space,Str "He",Space,Str "had",Space,Str "a",Space,Str "lot",Space,Str "of",Space,Str "things",Space,Str "to",LineBreak,Str "say",Str ",",Space,Str "so",Space,Str "the",Space,Str "text",Space,Str "is",Space,Str "really",Space,Str "really",Space,Str "long",Space,Str "and",Space,Str "spans",Space,Str "on",Space,Str "multiple",Space,Str "lines",Str "."]]
-,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph",Str "."]
+ [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "famous",Space,Str "quote",Space,Str "from",Space,Str "somebody.",Space,Str "He",Space,Str "had",Space,Str "a",Space,Str "lot",Space,Str "of",Space,Str "things",Space,Str "to",LineBreak,Str "say,",Space,Str "so",Space,Str "the",Space,Str "text",Space,Str "is",Space,Str "really",Space,Str "really",Space,Str "long",Space,Str "and",Space,Str "spans",Space,Str "on",Space,Str "multiple",Space,Str "lines."]]
+,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
,Header 1 ("code-blocks",[],[]) [Str "Code",Space,Str "Blocks"]
-,Para [Str "Code",Str ":"]
+,Para [Str "Code:"]
,CodeBlock ("",[],[]) " ---- (should be four hyphens)\n\n sub status {\n print \"working\";\n }\n\n this code block is indented by one tab"
-,Para [Str "And",Str ":"]
+,Para [Str "And:"]
,CodeBlock ("",[],[]) " this code block is indented by two tabs\n\n These should not be escaped: \\$ \\\\ \\> \\[ \\{"
,CodeBlock ("",[],[]) "Code block with .bc\n continued\n @</\\\n"
-,Para [Str "Inline",Space,Str "code",Str ":",Space,Code ("",[],[]) "<tt>",Str ",",Space,Code ("",[],[]) "@",Str "."]
+,Para [Str "Inline",Space,Str "code:",Space,Code ("",[],[]) "<tt>",Str ",",Space,Code ("",[],[]) "@",Str "."]
,Header 1 ("notextile",[],[]) [Str "Notextile"]
,Para [Str "A",Space,Str "block",Space,Str "of",Space,Str "text",Space,Str "can",Space,Str "be",Space,Str "protected",Space,Str "with",Space,Str "notextile",Space,Str ":"]
,Para [Str "\nNo *bold* and\n* no bullet\n"]
-,Para [Str "and",Space,Str "inlines",Space,Str "can",Space,Str "be",Space,Str "protected",Space,Str "with",Space,Str "double *equals (=)* markup",Str "."]
+,Para [Str "and",Space,Str "inlines",Space,Str "can",Space,Str "be",Space,Str "protected",Space,Str "with",Space,Str "double *equals (=)* markup."]
,Header 1 ("lists",[],[]) [Str "Lists"]
,Header 2 ("unordered",[],[]) [Str "Unordered"]
-,Para [Str "Asterisks",Space,Str "tight",Str ":"]
+,Para [Str "Asterisks",Space,Str "tight:"]
,BulletList
[[Plain [Str "asterisk",Space,Str "1"]]
,[Plain [Str "asterisk",Space,Str "2"]]
,[Plain [Str "asterisk",Space,Str "3"]]]
-,Para [Str "With",Space,Str "line",Space,Str "breaks",Str ":"]
+,Para [Str "With",Space,Str "line",Space,Str "breaks:"]
,BulletList
[[Plain [Str "asterisk",Space,Str "1",LineBreak,Str "newline"]]
,[Plain [Str "asterisk",Space,Str "2"]]]
,Header 2 ("ordered",[],[]) [Str "Ordered"]
-,Para [Str "Tight",Str ":"]
+,Para [Str "Tight:"]
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "First"]]
,[Plain [Str "Second"]]
@@ -52,42 +52,42 @@ Pandoc (Meta {unMeta = fromList []})
,BulletList
[[Plain [Str "ui",Space,Str "1"]
,BulletList
- [[Plain [Str "ui",Space,Str "1",Str ".",Str "1"]
+ [[Plain [Str "ui",Space,Str "1.1"]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Plain [Str "oi",Space,Str "1",Str ".",Str "1",Str ".",Str "1"]]
- ,[Plain [Str "oi",Space,Str "1",Str ".",Str "1",Str ".",Str "2"]]]]
- ,[Plain [Str "ui",Space,Str "1",Str ".",Str "2"]]]]
+ [[Plain [Str "oi",Space,Str "1.1.1"]]
+ ,[Plain [Str "oi",Space,Str "1.1.2"]]]]
+ ,[Plain [Str "ui",Space,Str "1.2"]]]]
,[Plain [Str "ui",Space,Str "2"]
,OrderedList (1,DefaultStyle,DefaultDelim)
- [[Plain [Str "oi",Space,Str "2",Str ".",Str "1"]
+ [[Plain [Str "oi",Space,Str "2.1"]
,BulletList
- [[Plain [Str "ui",Space,Str "2",Str ".",Str "1",Str ".",Str "1"]]
- ,[Plain [Str "ui",Space,Str "2",Str ".",Str "1",Str ".",Str "2"]]]]]]]
+ [[Plain [Str "ui",Space,Str "2.1.1"]]
+ ,[Plain [Str "ui",Space,Str "2.1.2"]]]]]]]
,Header 2 ("definition-list",[],[]) [Str "Definition",Space,Str "List"]
,DefinitionList
[([Str "coffee"],
[[Plain [Str "Hot",Space,Str "and",Space,Str "black"]]])
,([Str "tea"],
- [[Plain [Str "Also",Space,Str "hot",Str ",",Space,Str "but",Space,Str "a",Space,Str "little",Space,Str "less",Space,Str "black"]]])
+ [[Plain [Str "Also",Space,Str "hot,",Space,Str "but",Space,Str "a",Space,Str "little",Space,Str "less",Space,Str "black"]]])
,([Str "milk"],
- [[Para [Str "Nourishing",Space,Str "beverage",Space,Str "for",Space,Str "baby",Space,Str "cows",Str "."]
- ,Para [Str "Cold",Space,Str "drink",Space,Str "that",Space,Str "goes",Space,Str "great",Space,Str "with",Space,Str "cookies",Str "."]]])
+ [[Para [Str "Nourishing",Space,Str "beverage",Space,Str "for",Space,Str "baby",Space,Str "cows."]
+ ,Para [Str "Cold",Space,Str "drink",Space,Str "that",Space,Str "goes",Space,Str "great",Space,Str "with",Space,Str "cookies."]]])
,([Str "beer"],
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
-,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "Hyphenated-words-are-ok",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation",Str ".",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
-,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
-,Para [Str "Superscripts",Str ":",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts",Str ":",Space,Subscript [Str "here"],Space,Str "H",Subscript [Str "2"],Str "O",Str ",",Space,Str "H",Subscript [Str "23"],Str "O",Str ",",Space,Str "H",Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O",Str "."]
-,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes",Str "."]
-,Para [Str "Elipses",Space,Str ":",Space,Str "He",Space,Str "thought",Space,Str "and",Space,Str "thought",Space,Str "\8230",Space,Str "and",Space,Str "then",Space,Str "thought",Space,Str "some",Space,Str "more",Str "."]
-,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Quoted DoubleQuote [Str "I",Str "\8217",Str "d",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you"],Space,Str "for",Space,Str "example",Str "."]
+,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "Hyphenated-words-are-ok,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation.",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
+,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
+,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Space,Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts:",Space,Subscript [Str "here"],Space,Str "H",Space,Subscript [Str "2"],Str "O,",Space,Str "H",Space,Subscript [Str "23"],Str "O,",Space,Str "H",Space,Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O."]
+,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes."]
+,Para [Str "Elipses",Space,Str ":",Space,Str "He",Space,Str "thought",Space,Str "and",Space,Str "thought",Space,Str "\8230",Space,Str "and",Space,Str "then",Space,Str "thought",Space,Str "some",Space,Str "more."]
+,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Quoted DoubleQuote [Str "I\8217d",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you"],Space,Str "for",Space,Str "example."]
,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "url"] ("http://www.url.com","")]
,Para [Link [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")]
,Para [Str "Automatic",Space,Str "linking",Space,Str "to",Space,Link [Str "http://www.example.com"] ("http://www.example.com",""),Str "."]
-,Para [Link [Str "Example"] ("http://www.example.com/",""),Str ":",Space,Str "Example",Space,Str "of",Space,Str "a",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "colon",Str "."]
-,Para [Str "A",Space,Str "link",Link [Str "with",Space,Str "brackets"] ("http://www.example.com",""),Str "and",Space,Str "no",Space,Str "spaces",Str "."]
+,Para [Link [Str "Example"] ("http://www.example.com/",""),Str ":",Space,Str "Example",Space,Str "of",Space,Str "a",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "colon."]
+,Para [Str "A",Space,Str "link",Link [Str "with",Space,Str "brackets"] ("http://www.example.com",""),Str "and",Space,Str "no",Space,Str "spaces."]
,Header 1 ("tables",[],[]) [Str "Tables"]
,Para [Str "Textile",Space,Str "allows",Space,Str "tables",Space,Str "with",Space,Str "and",Space,Str "without",Space,Str "headers",Space,Str ":"]
,Header 2 ("without-headers",[],[]) [Str "Without",Space,Str "headers"]
@@ -121,11 +121,11 @@ Pandoc (Meta {unMeta = fromList []})
,[Plain [Str "45"]]
,[Plain [Str "f"]]]]
,Header 1 ("images",[],[]) [Str "Images"]
-,Para [Str "Textile",Space,Str "inline",Space,Str "image",Space,Str "syntax",Str ",",Space,Str "like",Space,LineBreak,Str "here",Space,Image [Str "this is the alt text"] ("this_is_an_image.png","this is the alt text"),LineBreak,Str "and",Space,Str "here",Space,Image [Str ""] ("this_is_an_image.png",""),Str "."]
+,Para [Str "Textile",Space,Str "inline",Space,Str "image",Space,Str "syntax,",Space,Str "like",LineBreak,Str "here",Space,Image [Str "this is the alt text"] ("this_is_an_image.png","this is the alt text"),LineBreak,Str "and",Space,Str "here",Space,Image [Str ""] ("this_is_an_image.png",""),Str "."]
,Header 1 ("attributes",[],[]) [Str "Attributes"]
-,Header 2 ("ident",["bar","foo"],[("style","color:red"),("lang","en")]) [Str "HTML",Space,Str "and",Space,Str "CSS",Space,Str "attributes",Space,Str "are",Space,Str "parsed",Space,Str "in",Space,Str "headers",Str "."]
+,Header 2 ("ident",["bar","foo"],[("style","color:red"),("lang","en")]) [Str "HTML",Space,Str "and",Space,Str "CSS",Space,Str "attributes",Space,Str "are",Space,Str "parsed",Space,Str "in",Space,Str "headers."]
,Para [Str "as",Space,Str "well",Space,Str "as",Space,Strong [Str "inline",Space,Str "attributes"],Space,Str "of",Space,Str " all kind"]
-,Para [Str "and",Space,Str "paragraph",Space,Str "attributes",Str ",",Space,Str "and",Space,Str "table",Space,Str "attributes",Str "."]
+,Para [Str "and",Space,Str "paragraph",Space,Str "attributes,",Space,Str "and",Space,Str "table",Space,Str "attributes."]
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
[]
[[[Plain [Str "name"]]
@@ -137,7 +137,7 @@ Pandoc (Meta {unMeta = fromList []})
,Header 1 ("entities",[],[]) [Str "Entities"]
,Para [Str "*",LineBreak,Str "&"]
,Header 1 ("raw-html",[],[]) [Str "Raw",Space,Str "HTML"]
-,Para [Str "However",Str ",",Space,RawInline (Format "html") "<strong>",Space,Str "raw",Space,Str "HTML",Space,Str "inlines",Space,RawInline (Format "html") "</strong>",Space,Str "are",Space,Str "accepted",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str ":"]
+,Para [Str "However,",Space,RawInline (Format "html") "<strong>",Space,Str "raw",Space,Str "HTML",Space,Str "inlines",Space,RawInline (Format "html") "</strong>",Space,Str "are",Space,Str "accepted,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str ":"]
,RawBlock (Format "html") "<div class=\"foobar\">"
,Para [Str "any",Space,Strong [Str "Raw",Space,Str "HTML",Space,Str "Block"],Space,Str "with",Space,Str "bold"]
,RawBlock (Format "html") "</div>"
@@ -145,9 +145,9 @@ Pandoc (Meta {unMeta = fromList []})
,RawBlock (Format "html") "<div>"
,Para [Str "inlined"]
,RawBlock (Format "html") "</div>"
-,Para [Str "as",Space,Str "well",Str "."]
+,Para [Str "as",Space,Str "well."]
,BulletList
- [[Plain [Str "this",Space,Str "<",Str "div",Str ">",Space,Str "won",Str "\8217",Str "t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,Str "<",Str "/div",Str ">"]]
+ [[Plain [Str "this",Space,Str "<div>",Space,Str "won\8217t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,Str "</div>"]]
,[Plain [Str "but",Space,Str "this",Space,RawInline (Format "html") "<strong>",Space,Str "will",Space,Str "produce",Space,Str "inline",Space,Str "html",Space,RawInline (Format "html") "</strong>"]]]
,Para [Str "Can",Space,Str "you",Space,Str "prove",Space,Str "that",Space,Str "2",Space,Str "<",Space,Str "3",Space,Str "?"]
,Header 1 ("raw-latex",[],[]) [Str "Raw",Space,Str "LaTeX"]
@@ -156,12 +156,11 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "and",Space,Str "for",Space,RawInline (Format "latex") "\\emph{inlines}",Str "."]
,Header 1 ("acronyms-and-marks",[],[]) [Str "Acronyms",Space,Str "and",Space,Str "marks"]
,Para [Str "PBS (Public Broadcasting System)"]
-,Para [Str "Hi",Str "\8482"]
+,Para [Str "Hi\8482"]
,Para [Str "Hi",Space,Str "\8482"]
-,Para [Str "\174",Space,Str "Hi",Str "\174"]
-,Para [Str "Hi",Str "\169",Str "2008",Space,Str "\169",Space,Str "2008"]
+,Para [Str "\174",Space,Str "Hi\174"]
+,Para [Str "Hi\169\&2008",Space,Str "\169",Space,Str "2008"]
,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
-,Para [Str "A",Space,Str "note",Str ".",Note [Para [Str "The",Space,Str "note",LineBreak,Str "is",Space,Str "here",Str "!"]],Space,Str "Another",Space,Str "note",Note [Para [Str "Other",Space,Str "note",Str "."]],Str "."]
+,Para [Str "A",Space,Str "note.",Note [Para [Str "The",Space,Str "note",LineBreak,Str "is",Space,Str "here!"]],Space,Str "Another",Space,Str "note",Note [Para [Str "Other",Space,Str "note."]],Str "."]
,Header 1 ("comment-blocks",[],[]) [Str "Comment",Space,Str "blocks"]
-,Null
-,Para [Str "not",Space,Str "a",Space,Str "comment",Str "."]]
+,Para [Str "not",Space,Str "a",Space,Str "comment."]]
diff --git a/tests/textile-reader.textile b/tests/textile-reader.textile
index e31052b6a..73c36b0d1 100644
--- a/tests/textile-reader.textile
+++ b/tests/textile-reader.textile
@@ -139,8 +139,8 @@ _*This is strong and em.*_
So is *_this_* word and __**that one**__.
-This is strikeout and *strong*-
-Superscripts: a[^bc^]d a^*hello*^ a[^hello there^].
-Subscripts: ~here~ H[~2~]O, H[~23~]O, H[~many of them~]O.
+Superscripts: a[^bc^]d a ^*hello*^ a[^hello there^].
+Subscripts: ~here~ H[ ~2~]O, H[ ~23~]O, H[ ~many of them~]O.
Dashes : How cool -- automatic dashes.
@@ -187,7 +187,7 @@ h2. With headers
h1. Images
-Textile inline image syntax, like
+Textile inline image syntax, like
here !this_is_an_image.png(this is the alt text)!
and here !this_is_an_image.png!.