RST writer: separate inline transformation logic from writing logic (#4438)
This is to help enable solutions solutions to #4434 and #4368.
This commit is contained in:
parent
65cc909fde
commit
90a705c8af
1 changed files with 22 additions and 18 deletions
|
@ -46,6 +46,7 @@ import Text.Pandoc.Pretty
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import Text.Pandoc.Templates (renderTemplate')
|
import Text.Pandoc.Templates (renderTemplate')
|
||||||
import Text.Pandoc.Writers.Shared
|
import Text.Pandoc.Writers.Shared
|
||||||
|
import Text.Pandoc.Walk
|
||||||
|
|
||||||
type Refs = [([Inline], Target)]
|
type Refs = [([Inline], Target)]
|
||||||
|
|
||||||
|
@ -376,13 +377,9 @@ blockListToRST :: PandocMonad m
|
||||||
-> RST m Doc
|
-> RST m Doc
|
||||||
blockListToRST = blockListToRST' False
|
blockListToRST = blockListToRST' False
|
||||||
|
|
||||||
-- | Convert list of Pandoc inline elements to RST.
|
transformInlines :: [Inline] -> [Inline]
|
||||||
inlineListToRST :: PandocMonad m => [Inline] -> RST m Doc
|
transformInlines =
|
||||||
inlineListToRST lst =
|
removeLeadingTrailingSpace . removeSpaceAfterDisplayMath . insertBS
|
||||||
mapM inlineToRST ((stripLeadingTrailingSpace .
|
|
||||||
removeSpaceAfterDisplayMath .
|
|
||||||
insertBS) lst) >>=
|
|
||||||
return . hcat
|
|
||||||
where -- remove spaces after displaymath, as they screw up indentation:
|
where -- remove spaces after displaymath, as they screw up indentation:
|
||||||
removeSpaceAfterDisplayMath (Math DisplayMath x : zs) =
|
removeSpaceAfterDisplayMath (Math DisplayMath x : zs) =
|
||||||
Math DisplayMath x : dropWhile (==Space) zs
|
Math DisplayMath x : dropWhile (==Space) zs
|
||||||
|
@ -438,44 +435,51 @@ inlineListToRST lst =
|
||||||
isComplex (Span _ (x:_)) = isComplex x
|
isComplex (Span _ (x:_)) = isComplex x
|
||||||
isComplex _ = False
|
isComplex _ = False
|
||||||
|
|
||||||
|
inlineListToRST :: PandocMonad m => [Inline] -> RST m Doc
|
||||||
|
inlineListToRST = writeInlines . walk transformInlines
|
||||||
|
|
||||||
|
-- | Convert list of Pandoc inline elements to RST.
|
||||||
|
writeInlines :: PandocMonad m => [Inline] -> RST m Doc
|
||||||
|
writeInlines lst = mapM inlineToRST lst >>= return . hcat
|
||||||
|
|
||||||
-- | Convert Pandoc inline element to RST.
|
-- | Convert Pandoc inline element to RST.
|
||||||
inlineToRST :: PandocMonad m => Inline -> RST m Doc
|
inlineToRST :: PandocMonad m => Inline -> RST m Doc
|
||||||
inlineToRST (Span (_,_,kvs) ils) = do
|
inlineToRST (Span (_,_,kvs) ils) = do
|
||||||
contents <- inlineListToRST ils
|
contents <- writeInlines ils
|
||||||
return $
|
return $
|
||||||
case lookup "role" kvs of
|
case lookup "role" kvs of
|
||||||
Just role -> ":" <> text role <> ":`" <> contents <> "`"
|
Just role -> ":" <> text role <> ":`" <> contents <> "`"
|
||||||
Nothing -> contents
|
Nothing -> contents
|
||||||
inlineToRST (Emph lst) = do
|
inlineToRST (Emph lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
return $ "*" <> contents <> "*"
|
return $ "*" <> contents <> "*"
|
||||||
inlineToRST (Strong lst) = do
|
inlineToRST (Strong lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
return $ "**" <> contents <> "**"
|
return $ "**" <> contents <> "**"
|
||||||
inlineToRST (Strikeout lst) = do
|
inlineToRST (Strikeout lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
return $ "[STRIKEOUT:" <> contents <> "]"
|
return $ "[STRIKEOUT:" <> contents <> "]"
|
||||||
inlineToRST (Superscript lst) = do
|
inlineToRST (Superscript lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
return $ ":sup:`" <> contents <> "`"
|
return $ ":sup:`" <> contents <> "`"
|
||||||
inlineToRST (Subscript lst) = do
|
inlineToRST (Subscript lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
return $ ":sub:`" <> contents <> "`"
|
return $ ":sub:`" <> contents <> "`"
|
||||||
inlineToRST (SmallCaps lst) = inlineListToRST lst
|
inlineToRST (SmallCaps lst) = writeInlines lst
|
||||||
inlineToRST (Quoted SingleQuote lst) = do
|
inlineToRST (Quoted SingleQuote lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
opts <- gets stOptions
|
opts <- gets stOptions
|
||||||
if isEnabled Ext_smart opts
|
if isEnabled Ext_smart opts
|
||||||
then return $ "'" <> contents <> "'"
|
then return $ "'" <> contents <> "'"
|
||||||
else return $ "‘" <> contents <> "’"
|
else return $ "‘" <> contents <> "’"
|
||||||
inlineToRST (Quoted DoubleQuote lst) = do
|
inlineToRST (Quoted DoubleQuote lst) = do
|
||||||
contents <- inlineListToRST lst
|
contents <- writeInlines lst
|
||||||
opts <- gets stOptions
|
opts <- gets stOptions
|
||||||
if isEnabled Ext_smart opts
|
if isEnabled Ext_smart opts
|
||||||
then return $ "\"" <> contents <> "\""
|
then return $ "\"" <> contents <> "\""
|
||||||
else return $ "“" <> contents <> "”"
|
else return $ "“" <> contents <> "”"
|
||||||
inlineToRST (Cite _ lst) =
|
inlineToRST (Cite _ lst) =
|
||||||
inlineListToRST lst
|
writeInlines lst
|
||||||
inlineToRST (Code _ str) = do
|
inlineToRST (Code _ str) = do
|
||||||
opts <- gets stOptions
|
opts <- gets stOptions
|
||||||
-- we trim the string because the delimiters must adjoin a
|
-- we trim the string because the delimiters must adjoin a
|
||||||
|
@ -526,7 +530,7 @@ inlineToRST (Link _ [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do
|
||||||
return $ "|" <> label <> "|"
|
return $ "|" <> label <> "|"
|
||||||
inlineToRST (Link _ txt (src, tit)) = do
|
inlineToRST (Link _ txt (src, tit)) = do
|
||||||
useReferenceLinks <- gets $ writerReferenceLinks . stOptions
|
useReferenceLinks <- gets $ writerReferenceLinks . stOptions
|
||||||
linktext <- inlineListToRST $ B.toList . B.trimInlines . B.fromList $ txt
|
linktext <- writeInlines $ B.toList . B.trimInlines . B.fromList $ txt
|
||||||
if useReferenceLinks
|
if useReferenceLinks
|
||||||
then do refs <- gets stLinks
|
then do refs <- gets stLinks
|
||||||
case lookup txt refs of
|
case lookup txt refs of
|
||||||
|
|
Loading…
Reference in a new issue