aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlexander Krotov <ilabdsf@gmail.com>2017-11-24 12:17:20 +0300
committerAlexander Krotov <ilabdsf@gmail.com>2017-11-24 12:17:20 +0300
commit0cfd764d27bc03b59871e477d6bfd7341f4916b0 (patch)
treebe7d4dda1613f1a8d7a563d6345bac50e6334342
parentcd85c73ded2b100d33d3c1d36eac182bdd593b2f (diff)
downloadpandoc-0cfd764d27bc03b59871e477d6bfd7341f4916b0.tar.gz
Muse: move inline list normalization to writer
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs22
-rw-r--r--src/Text/Pandoc/Writers/Muse.hs10
-rw-r--r--test/Tests/Readers/Muse.hs2
-rw-r--r--test/Tests/Writers/Muse.hs1
4 files changed, 14 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index 11fea5fde..a3cb40e58 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -139,20 +139,6 @@ parseHtmlContentWithAttrs tag parser = do
parseHtmlContent :: PandocMonad m => String -> MuseParser m a -> MuseParser m [a]
parseHtmlContent tag p = fmap snd (parseHtmlContentWithAttrs tag p)
-normalizeInlineList :: [Inline] -> [Inline]
-normalizeInlineList (Code a1 x1 : Code a2 x2 : ils) | a1 == a2
- = normalizeInlineList $ Code a1 (x1 ++ x2) : ils
-normalizeInlineList (RawInline f1 x1 : RawInline f2 x2 : ils) | f1 == f2
- = normalizeInlineList $ RawInline f1 (x1 ++ x2) : ils
-normalizeInlineList (x:xs) = x : normalizeInlineList xs
-normalizeInlineList [] = []
-
-normalizeInlines :: Inlines -> Inlines
-normalizeInlines = B.fromList . normalizeInlineList . B.toList . B.trimInlines
-
-normalizeInlinesF :: Future s Inlines -> Future s Inlines
-normalizeInlinesF = liftM normalizeInlines
-
--
-- directive parsers
--
@@ -164,7 +150,7 @@ parseDirective = do
space
spaces
raw <- manyTill anyChar eol
- value <- parseFromString (normalizeInlinesF . mconcat <$> many inline) raw
+ value <- parseFromString (trimInlinesF . mconcat <$> many inline) raw
return (key, value)
directive :: PandocMonad m => MuseParser m ()
@@ -231,7 +217,7 @@ header = try $ do
level <- fmap length $ many1 $ char '*'
guard $ level <= 5
spaceChar
- content <- normalizeInlinesF . mconcat <$> manyTill inline eol
+ content <- trimInlinesF . mconcat <$> manyTill inline eol
attr <- registerHeader ("", [], []) (runF content defaultParserState)
return $ B.headerWith attr level <$> content
@@ -300,7 +286,7 @@ verseLines :: PandocMonad m => MuseParser m (F Blocks)
verseLines = do
optionMaybe blankline -- Skip blankline after opening tag on separate line
lns <- many verseLine
- lns' <- mapM (parseFromString' (normalizeInlinesF . mconcat <$> many inline)) lns
+ lns' <- mapM (parseFromString' (trimInlinesF . mconcat <$> many inline)) lns
return $ B.lineBlock <$> sequence lns'
verseTag :: PandocMonad m => MuseParser m (F Blocks)
@@ -317,7 +303,7 @@ para = do
indent <- length <$> many spaceChar
st <- stateParserContext <$> getState
let f = if st /= ListItemState && indent >= 2 && indent < 6 then B.blockQuote else id
- fmap (f . B.para) . normalizeInlinesF . mconcat <$> many1Till inline endOfParaElement
+ fmap (f . B.para) . trimInlinesF . mconcat <$> many1Till inline endOfParaElement
where
endOfParaElement = lookAhead $ endOfInput <|> endOfPara <|> newBlockElement
endOfInput = try $ skipMany blankline >> skipSpaces >> eof
diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs
index a6ef28ba7..ed5ad5793 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -291,11 +291,19 @@ conditionalEscapeString s =
then escapeString s
else s
+normalizeInlineList :: [Inline] -> [Inline]
+normalizeInlineList (Code a1 x1 : Code a2 x2 : ils) | a1 == a2
+ = normalizeInlineList $ Code a1 (x1 ++ x2) : ils
+normalizeInlineList (RawInline f1 x1 : RawInline f2 x2 : ils) | f1 == f2
+ = normalizeInlineList $ RawInline f1 (x1 ++ x2) : ils
+normalizeInlineList (x:xs) = x : normalizeInlineList xs
+normalizeInlineList [] = []
+
-- | Convert list of Pandoc inline elements to Muse.
inlineListToMuse :: PandocMonad m
=> [Inline]
-> StateT WriterState m Doc
-inlineListToMuse lst = liftM hcat (mapM inlineToMuse lst)
+inlineListToMuse lst = liftM hcat (mapM inlineToMuse (normalizeInlineList lst))
-- | Convert Pandoc inline element to Muse.
inlineToMuse :: PandocMonad m
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index 65665c1d2..3e4b89207 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -125,8 +125,6 @@ tests =
, "Verbatim inside code" =: "<code><verbatim>foo</verbatim></code>" =?> para (code "<verbatim>foo</verbatim>")
- , "Code normalization" =: "<code><code><</code><code>/code></code>" =?> para (code "<code></code>")
-
, testGroup "Links"
[ "Link without description" =:
"[[https://amusewiki.org/]]" =?>
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index 562cccfe5..b5931b7db 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -300,6 +300,7 @@ tests = [ testGroup "block elements"
, testGroup "code"
[ "simple" =: code "foo" =?> "<code>foo</code>"
, "escape tag" =: code "<code>foo = bar</code> baz" =?> "<code><code>foo = bar<</code><code>/code> baz</code>"
+ , "normalization" =: code "</co" <> code "de>" =?> "<code><</code><code>/code></code>"
]
, testGroup "spaces"
[ "space" =: text "a" <> space <> text "b" =?> "a b"