Muse writer: expand math before inline list normalization

This commit is contained in:
Alexander Krotov 2018-03-05 19:38:11 +03:00
parent 7518e8e00e
commit 7da6e4390c
2 changed files with 14 additions and 3 deletions

View file

@ -291,6 +291,14 @@ conditionalEscapeString s =
then escapeString s
else s
-- Expand Math before normalizing inline list
preprocessInlineList :: PandocMonad m
=> [Inline]
-> m [Inline]
preprocessInlineList (Math t str:xs) = (++ xs) <$> texMathToInlines t str
preprocessInlineList (x:xs) = (x:) <$> preprocessInlineList xs
preprocessInlineList [] = return []
normalizeInlineList :: [Inline] -> [Inline]
normalizeInlineList (x : Str "" : xs)
= normalizeInlineList (x:xs)
@ -327,7 +335,9 @@ fixNotes (x:xs) = x : fixNotes xs
inlineListToMuse :: PandocMonad m
=> [Inline]
-> StateT WriterState m Doc
inlineListToMuse lst = hcat <$> mapM inlineToMuse (fixNotes $ normalizeInlineList lst)
inlineListToMuse lst = do
lst' <- preprocessInlineList lst
hcat <$> mapM inlineToMuse (fixNotes $ normalizeInlineList lst')
-- | Convert Pandoc inline element to Muse.
inlineToMuse :: PandocMonad m
@ -363,8 +373,8 @@ inlineToMuse (Quoted DoubleQuote lst) = do
inlineToMuse (Cite _ lst) = inlineListToMuse lst
inlineToMuse (Code _ str) = return $
"<code>" <> text (substitute "</code>" "<</code><code>/code>" str) <> "</code>"
inlineToMuse (Math t str) =
lift (texMathToInlines t str) >>= inlineListToMuse
inlineToMuse Math{} =
fail "Math should be expanded before normalization"
inlineToMuse (RawInline (Format f) str) =
return $ "<literal style=\"" <> text f <> "\">" <> text str <> "</literal>"
inlineToMuse LineBreak = return $ "<br>" <> cr

View file

@ -332,6 +332,7 @@ tests = [ testGroup "block elements"
[ "inline math" =: math "2^3" =?> "2<sup>3</sup>"
, "display math" =: displayMath "2^3" =?> "2<sup>3</sup>"
, "multiple letters in inline math" =: math "abc" =?> "<em>abc</em>"
, "expand math before normalization" =: math "[" <> str "2]" =?> "<verbatim>[2]</verbatim>"
]
, "raw inline"
=: rawInline "html" "<mark>marked text</mark>"