Modified readers to emit SoftBreak when appropriate.
This commit is contained in:
parent
d9c2f500bf
commit
af7e782436
14 changed files with 26 additions and 16 deletions
|
@ -103,7 +103,7 @@ addInline (Node _ (TEXT t) _) = (map toinl clumps ++)
|
||||||
toinl (' ':_) = Space
|
toinl (' ':_) = Space
|
||||||
toinl xs = Str xs
|
toinl xs = Str xs
|
||||||
addInline (Node _ LINEBREAK _) = (LineBreak :)
|
addInline (Node _ LINEBREAK _) = (LineBreak :)
|
||||||
addInline (Node _ SOFTBREAK _) = (Space :)
|
addInline (Node _ SOFTBREAK _) = (SoftBreak :)
|
||||||
addInline (Node _ (INLINE_HTML t) _) =
|
addInline (Node _ (INLINE_HTML t) _) =
|
||||||
(RawInline (Format "html") (unpack t) :)
|
(RawInline (Format "html") (unpack t) :)
|
||||||
addInline (Node _ (CODE t) _) =
|
addInline (Node _ (CODE t) _) =
|
||||||
|
|
|
@ -799,7 +799,10 @@ pBad = do
|
||||||
return $ B.str [c']
|
return $ B.str [c']
|
||||||
|
|
||||||
pSpace :: InlinesParser Inlines
|
pSpace :: InlinesParser Inlines
|
||||||
pSpace = many1 (satisfy isSpace) >> return B.space
|
pSpace = many1 (satisfy isSpace) >>= \xs ->
|
||||||
|
if '\n' `elem` xs
|
||||||
|
then return B.softbreak
|
||||||
|
else return B.space
|
||||||
|
|
||||||
--
|
--
|
||||||
-- Constants
|
-- Constants
|
||||||
|
|
|
@ -100,8 +100,13 @@ dimenarg = try $ do
|
||||||
return $ ch ++ num ++ dim
|
return $ ch ++ num ++ dim
|
||||||
|
|
||||||
sp :: LP ()
|
sp :: LP ()
|
||||||
sp = skipMany1 $ satisfy (\c -> c == ' ' || c == '\t')
|
sp = whitespace <|> endline
|
||||||
<|> try (newline <* lookAhead anyChar <* notFollowedBy blankline)
|
|
||||||
|
whitespace :: LP ()
|
||||||
|
whitespace = skipMany1 $ satisfy (\c -> c == ' ' || c == '\t')
|
||||||
|
|
||||||
|
endline :: LP ()
|
||||||
|
endline = try (newline >> lookAhead anyChar >> notFollowedBy blankline)
|
||||||
|
|
||||||
isLowerHex :: Char -> Bool
|
isLowerHex :: Char -> Bool
|
||||||
isLowerHex x = x >= '0' && x <= '9' || x >= 'a' && x <= 'f'
|
isLowerHex x = x >= '0' && x <= '9' || x >= 'a' && x <= 'f'
|
||||||
|
@ -196,7 +201,8 @@ singleQuote = do
|
||||||
|
|
||||||
inline :: LP Inlines
|
inline :: LP Inlines
|
||||||
inline = (mempty <$ comment)
|
inline = (mempty <$ comment)
|
||||||
<|> (space <$ sp)
|
<|> (space <$ whitespace)
|
||||||
|
<|> (softbreak <$ endline)
|
||||||
<|> inlineText
|
<|> inlineText
|
||||||
<|> inlineCommand
|
<|> inlineCommand
|
||||||
<|> inlineEnvironment
|
<|> inlineEnvironment
|
||||||
|
|
|
@ -555,7 +555,8 @@ inlineHtml :: MWParser Inlines
|
||||||
inlineHtml = B.rawInline "html" . snd <$> htmlTag isInlineTag'
|
inlineHtml = B.rawInline "html" . snd <$> htmlTag isInlineTag'
|
||||||
|
|
||||||
whitespace :: MWParser Inlines
|
whitespace :: MWParser Inlines
|
||||||
whitespace = B.space <$ (skipMany1 spaceChar <|> endline <|> htmlComment)
|
whitespace = B.space <$ (skipMany1 spaceChar <|> htmlComment)
|
||||||
|
<|> B.softbreak <$ endline
|
||||||
|
|
||||||
endline :: MWParser ()
|
endline :: MWParser ()
|
||||||
endline = () <$ try (newline <*
|
endline = () <$ try (newline <*
|
||||||
|
|
|
@ -1103,7 +1103,7 @@ endline = try $ do
|
||||||
decEmphasisNewlinesCount
|
decEmphasisNewlinesCount
|
||||||
guard =<< newlinesCountWithinLimits
|
guard =<< newlinesCountWithinLimits
|
||||||
updateLastPreCharPos
|
updateLastPreCharPos
|
||||||
return . return $ B.space
|
return . return $ B.softbreak
|
||||||
|
|
||||||
cite :: OrgParser (F Inlines)
|
cite :: OrgParser (F Inlines)
|
||||||
cite = try $ do
|
cite = try $ do
|
||||||
|
|
|
@ -1098,7 +1098,7 @@ endline = try $ do
|
||||||
then notFollowedBy (anyOrderedListMarker >> spaceChar) >>
|
then notFollowedBy (anyOrderedListMarker >> spaceChar) >>
|
||||||
notFollowedBy' bulletListStart
|
notFollowedBy' bulletListStart
|
||||||
else return ()
|
else return ()
|
||||||
return B.space
|
return B.softbreak
|
||||||
|
|
||||||
--
|
--
|
||||||
-- links
|
-- links
|
||||||
|
|
|
@ -550,7 +550,7 @@ endline = try $ do
|
||||||
notFollowedBy quote
|
notFollowedBy quote
|
||||||
notFollowedBy list
|
notFollowedBy list
|
||||||
notFollowedBy table
|
notFollowedBy table
|
||||||
return $ B.space
|
return $ B.softbreak
|
||||||
|
|
||||||
str :: T2T Inlines
|
str :: T2T Inlines
|
||||||
str = try $ do
|
str = try $ do
|
||||||
|
|
|
@ -9,7 +9,7 @@ packages:
|
||||||
- '.'
|
- '.'
|
||||||
- location:
|
- location:
|
||||||
git: 'https://github.com/jgm/pandoc-types'
|
git: 'https://github.com/jgm/pandoc-types'
|
||||||
commit: c46ab17eb17e16c3401a4ed48fc93e034a92b850
|
commit: 8aba9332f56fd23bc3c06065193abe5ace3e70b4
|
||||||
extra-dep: true
|
extra-dep: true
|
||||||
- location:
|
- location:
|
||||||
git: 'https://github.com/jgm/texmath'
|
git: 'https://github.com/jgm/texmath'
|
||||||
|
|
|
@ -260,7 +260,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
||||||
,Div ("",[],[])
|
,Div ("",[],[])
|
||||||
[Div ("",[],[])
|
[Div ("",[],[])
|
||||||
[Div ("",[],[])
|
[Div ("",[],[])
|
||||||
[Plain [Str "foo",SoftBreak]]]]
|
[Plain [Str "foo"]]]]
|
||||||
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
|
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
|
||||||
,RawBlock (Format "html") "<!-- Comment -->"
|
,RawBlock (Format "html") "<!-- Comment -->"
|
||||||
,Para [Str "Multiline:"]
|
,Para [Str "Multiline:"]
|
||||||
|
|
|
@ -912,7 +912,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
||||||
Now, nested:
|
Now, nested:
|
||||||
</para>
|
</para>
|
||||||
<para>
|
<para>
|
||||||
foo
|
foo
|
||||||
</para>
|
</para>
|
||||||
<para>
|
<para>
|
||||||
This should just be an HTML comment:
|
This should just be an HTML comment:
|
||||||
|
|
|
@ -350,7 +350,7 @@ As should this:
|
||||||
</code>
|
</code>
|
||||||
Now, nested:
|
Now, nested:
|
||||||
|
|
||||||
foo
|
foo
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -362,7 +362,7 @@ And this is <strong>strong</strong>
|
||||||
<div>
|
<div>
|
||||||
<div>
|
<div>
|
||||||
<div>
|
<div>
|
||||||
foo
|
foo
|
||||||
</div>
|
</div>
|
||||||
</div>
|
</div>
|
||||||
</div>
|
</div>
|
||||||
|
|
|
@ -374,7 +374,7 @@ Now, nested:
|
||||||
|
|
||||||
<div>
|
<div>
|
||||||
|
|
||||||
foo
|
foo
|
||||||
|
|
||||||
</div>
|
</div>
|
||||||
|
|
||||||
|
|
|
@ -424,7 +424,7 @@ Now, nested:
|
||||||
|
|
||||||
<div>
|
<div>
|
||||||
|
|
||||||
foo
|
foo
|
||||||
|
|
||||||
</div>
|
</div>
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue