Fixed asciidoc display math in list contexts.

This commit is contained in:
John MacFarlane 2019-02-09 11:02:19 -08:00
parent 8c2e2435f9
commit 4543543063
3 changed files with 48 additions and 19 deletions

View file

@ -56,12 +56,13 @@ import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
data WriterState = WriterState { defListMarker :: String data WriterState = WriterState { defListMarker :: String
, orderedListLevel :: Int , orderedListLevel :: Int
, bulletListLevel :: Int , bulletListLevel :: Int
, intraword :: Bool , intraword :: Bool
, autoIds :: Set.Set String , autoIds :: Set.Set String
, asciidoctorVariant :: Bool , asciidoctorVariant :: Bool
, inList :: Bool
, hasMath :: Bool , hasMath :: Bool
} }
@ -72,6 +73,7 @@ defaultWriterState = WriterState { defListMarker = "::"
, intraword = False , intraword = False
, autoIds = Set.empty , autoIds = Set.empty
, asciidoctorVariant = False , asciidoctorVariant = False
, inList = False
, hasMath = False , hasMath = False
} }
@ -268,7 +270,10 @@ blockToAsciiDoc opts (Table caption aligns widths headers rows) = do
return $ return $
caption'' $$ tablespec $$ border $$ head'' $$ body $$ border $$ blankline caption'' $$ tablespec $$ border $$ head'' $$ body $$ border $$ blankline
blockToAsciiDoc opts (BulletList items) = do blockToAsciiDoc opts (BulletList items) = do
inlist <- gets inList
modify $ \st -> st{ inList = True }
contents <- mapM (bulletListItemToAsciiDoc opts) items contents <- mapM (bulletListItemToAsciiDoc opts) items
modify $ \st -> st{ inList = inlist }
return $ cat contents <> blankline return $ cat contents <> blankline
blockToAsciiDoc opts (OrderedList (start, sty, _delim) items) = do blockToAsciiDoc opts (OrderedList (start, sty, _delim) items) = do
let listStyle = case sty of let listStyle = case sty of
@ -280,10 +285,16 @@ blockToAsciiDoc opts (OrderedList (start, sty, _delim) items) = do
let listoptions = case intercalate ", " (listStyle ++ listStart) of let listoptions = case intercalate ", " (listStyle ++ listStart) of
[] -> empty [] -> empty
x -> brackets (text x) x -> brackets (text x)
inlist <- gets inList
modify $ \st -> st{ inList = True }
contents <- mapM (orderedListItemToAsciiDoc opts) items contents <- mapM (orderedListItemToAsciiDoc opts) items
modify $ \st -> st{ inList = inlist }
return $ listoptions $$ cat contents <> blankline return $ listoptions $$ cat contents <> blankline
blockToAsciiDoc opts (DefinitionList items) = do blockToAsciiDoc opts (DefinitionList items) = do
inlist <- gets inList
modify $ \st -> st{ inList = True }
contents <- mapM (definitionListItemToAsciiDoc opts) items contents <- mapM (definitionListItemToAsciiDoc opts) items
modify $ \st -> st{ inList = inlist }
return $ cat contents <> blankline return $ cat contents <> blankline
blockToAsciiDoc opts (Div (ident,_,_) bs) = do blockToAsciiDoc opts (Div (ident,_,_) bs) = do
let identifier = if null ident then empty else "[[" <> text ident <> "]]" let identifier = if null ident then empty else "[[" <> text ident <> "]]"
@ -299,16 +310,31 @@ bulletListItemToAsciiDoc opts blocks = do
contents <- foldM (addBlock opts) empty blocks contents <- foldM (addBlock opts) empty blocks
modify $ \s -> s{ bulletListLevel = lev } modify $ \s -> s{ bulletListLevel = lev }
let marker = text (replicate (lev + 1) '*') let marker = text (replicate (lev + 1) '*')
return $ marker <> text " " <> contents <> cr return $ marker <> text " " <> listBegin blocks <>
contents <> cr
addBlock :: PandocMonad m => WriterOptions -> Doc -> Block -> ADW m Doc addBlock :: PandocMonad m => WriterOptions -> Doc -> Block -> ADW m Doc
addBlock opts d b | isEmpty d = chomp `fmap` blockToAsciiDoc opts b addBlock opts d b = do
addBlock opts d b@(BulletList _) = do x <- blockToAsciiDoc opts b x <- chomp <$> blockToAsciiDoc opts b
return $ d <> cr <> chomp x return $
addBlock opts d b@(OrderedList _ _) = do x <- blockToAsciiDoc opts b case b of
return $ d <> cr <> chomp x BulletList{} -> d <> cr <> x
addBlock opts d b = do x <- blockToAsciiDoc opts b OrderedList{} -> d <> cr <> x
return $ d <> cr <> text "+" <> cr <> chomp x Para (Math DisplayMath _:_) -> d <> cr <> x
Plain (Math DisplayMath _:_) -> d <> cr <> x
Para{} | isEmpty d -> x
Plain{} | isEmpty d -> x
_ -> d <> cr <> text "+" <> cr <> x
listBegin :: [Block] -> Doc
listBegin blocks =
case blocks of
Para (Math DisplayMath _:_) : _ -> "{blank}"
Plain (Math DisplayMath _:_) : _ -> "{blank}"
Para _ : _ -> empty
Plain _ : _ -> empty
_ : _ -> "{blank}"
[] -> "{blank}"
-- | Convert ordered list item (a list of blocks) to asciidoc. -- | Convert ordered list item (a list of blocks) to asciidoc.
orderedListItemToAsciiDoc :: PandocMonad m orderedListItemToAsciiDoc :: PandocMonad m
@ -321,7 +347,7 @@ orderedListItemToAsciiDoc opts blocks = do
contents <- foldM (addBlock opts) empty blocks contents <- foldM (addBlock opts) empty blocks
modify $ \s -> s{ orderedListLevel = lev } modify $ \s -> s{ orderedListLevel = lev }
let marker = text (replicate (lev + 1) '.') let marker = text (replicate (lev + 1) '.')
return $ marker <> text " " <> contents <> cr return $ marker <> text " " <> listBegin blocks <> contents <> cr
-- | Convert definition list item (label, list of blocks) to asciidoc. -- | Convert definition list item (label, list of blocks) to asciidoc.
definitionListItemToAsciiDoc :: PandocMonad m definitionListItemToAsciiDoc :: PandocMonad m
@ -437,10 +463,13 @@ inlineToAsciiDoc _ (Math DisplayMath str) = do
let content = if isAsciidoctor let content = if isAsciidoctor
then text str then text str
else "\\[" <> text str <> "\\]" else "\\[" <> text str <> "\\]"
inlist <- gets inList
let sepline = if inlist
then text "+"
else blankline
return $ return $
blankline <> "[latexmath]" $$ "++++" $$ (cr <> sepline) $$ "[latexmath]" $$ "++++" $$
content content $$ "++++" <> cr
$$ "++++" $$ blankline
inlineToAsciiDoc _ il@(RawInline f s) inlineToAsciiDoc _ il@(RawInline f s)
| f == "asciidoc" = return $ text s | f == "asciidoc" = return $ text s
| otherwise = do | otherwise = do

View file

@ -466,7 +466,7 @@ Ellipses…and…and….
* latexmath:[$223$] * latexmath:[$223$]
* latexmath:[$p$]-Tree * latexmath:[$p$]-Tree
* Heres some display math: * Heres some display math:
+
[latexmath] [latexmath]
++++ ++++
\[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\] \[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\]

View file

@ -467,7 +467,7 @@ Ellipses…and…and….
* latexmath:[223] * latexmath:[223]
* latexmath:[p]-Tree * latexmath:[p]-Tree
* Heres some display math: * Heres some display math:
+
[latexmath] [latexmath]
++++ ++++
\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h} \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}