summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/RST.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/RST.hs')
-rw-r--r--src/Text/Pandoc/Writers/RST.hs330
1 files changed, 190 insertions, 140 deletions
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 064434483..95cb46643 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-
-Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
+Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.RST
- Copyright : Copyright (C) 2006-2015 John MacFarlane
+ Copyright : Copyright (C) 2006-2018 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -31,19 +31,21 @@ Conversion of 'Pandoc' documents to reStructuredText.
reStructuredText: <http://docutils.sourceforge.net/rst.html>
-}
module Text.Pandoc.Writers.RST ( writeRST ) where
+import Control.Monad.State.Strict
+import Data.Char (isSpace, toLower)
+import Data.List (isPrefixOf, stripPrefix)
+import Data.Maybe (fromMaybe)
+import Data.Text (Text, stripEnd)
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
+import Text.Pandoc.ImageSize
+import Text.Pandoc.Logging
import Text.Pandoc.Options
+import Text.Pandoc.Pretty
import Text.Pandoc.Shared
-import Text.Pandoc.Writers.Shared
-import Text.Pandoc.ImageSize
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Builder (deleteMeta)
-import Data.Maybe (fromMaybe)
-import Data.List ( isPrefixOf, stripPrefix, intersperse, transpose )
-import Network.URI (isURI)
-import Text.Pandoc.Pretty
-import Control.Monad.State
-import Data.Char (isSpace, toLower)
+import Text.Pandoc.Writers.Shared
type Refs = [([Inline], Target)]
@@ -57,95 +59,99 @@ data WriterState =
, stTopLevel :: Bool
}
+type RST = StateT WriterState
+
-- | Convert Pandoc to RST.
-writeRST :: WriterOptions -> Pandoc -> String
-writeRST opts document =
+writeRST :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeRST opts document = do
let st = WriterState { stNotes = [], stLinks = [],
stImages = [], stHasMath = False,
stHasRawTeX = False, stOptions = opts,
- stTopLevel = True}
- in evalState (pandocToRST document) st
+ stTopLevel = True }
+ evalStateT (pandocToRST document) st
-- | Return RST representation of document.
-pandocToRST :: Pandoc -> State WriterState String
+pandocToRST :: PandocMonad m => Pandoc -> RST m Text
pandocToRST (Pandoc meta blocks) = do
- opts <- liftM stOptions get
+ opts <- gets stOptions
let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
+ let render' :: Doc -> Text
+ render' = render colwidth
let subtit = case lookupMeta "subtitle" meta of
Just (MetaBlocks [Plain xs]) -> xs
- _ -> []
+ _ -> []
title <- titleToRST (docTitle meta) subtit
metadata <- metaToJSON opts
- (fmap (render colwidth) . blockListToRST)
- (fmap (trimr . render colwidth) . inlineListToRST)
- $ deleteMeta "title" $ deleteMeta "subtitle" meta
+ (fmap render' . blockListToRST)
+ (fmap (stripEnd . render') . inlineListToRST)
+ $ B.deleteMeta "title" $ B.deleteMeta "subtitle" meta
body <- blockListToRST' True $ case writerTemplate opts of
Just _ -> normalizeHeadings 1 blocks
Nothing -> blocks
- notes <- liftM (reverse . stNotes) get >>= notesToRST
+ notes <- gets (reverse . stNotes) >>= notesToRST
-- note that the notes may contain refs, so we do them first
- refs <- liftM (reverse . stLinks) get >>= refsToRST
- pics <- liftM (reverse . stImages) get >>= pictRefsToRST
- hasMath <- liftM stHasMath get
- rawTeX <- liftM stHasRawTeX get
- let main = render colwidth $ foldl ($+$) empty $ [body, notes, refs, pics]
+ refs <- gets (reverse . stLinks) >>= refsToRST
+ pics <- gets (reverse . stImages) >>= pictRefsToRST
+ hasMath <- gets stHasMath
+ rawTeX <- gets stHasRawTeX
+ let main = render' $ foldl ($+$) empty [body, notes, refs, pics]
let context = defField "body" main
$ defField "toc" (writerTableOfContents opts)
$ defField "toc-depth" (show $ writerTOCDepth opts)
$ defField "math" hasMath
$ defField "title" (render Nothing title :: String)
$ defField "math" hasMath
- $ defField "rawtex" rawTeX
- $ metadata
+ $ defField "rawtex" rawTeX metadata
case writerTemplate opts of
Nothing -> return main
- Just tpl -> return $ renderTemplate' tpl context
+ Just tpl -> renderTemplate' tpl context
where
normalizeHeadings lev (Header l a i:bs) =
Header lev a i:normalizeHeadings (lev+1) cont ++ normalizeHeadings lev bs'
where (cont,bs') = break (headerLtEq l) bs
headerLtEq level (Header l' _ _) = l' <= level
- headerLtEq _ _ = False
+ headerLtEq _ _ = False
normalizeHeadings lev (b:bs) = b:normalizeHeadings lev bs
normalizeHeadings _ [] = []
-- | Return RST representation of reference key table.
-refsToRST :: Refs -> State WriterState Doc
+refsToRST :: PandocMonad m => Refs -> RST m Doc
refsToRST refs = mapM keyToRST refs >>= return . vcat
-- | Return RST representation of a reference key.
-keyToRST :: ([Inline], (String, String))
- -> State WriterState Doc
+keyToRST :: PandocMonad m => ([Inline], (String, String)) -> RST m Doc
keyToRST (label, (src, _)) = do
label' <- inlineListToRST label
- let label'' = if ':' `elem` ((render Nothing label') :: String)
+ let label'' = if ':' `elem` (render Nothing label' :: String)
then char '`' <> label' <> char '`'
else label'
return $ nowrap $ ".. _" <> label'' <> ": " <> text src
-- | Return RST representation of notes.
-notesToRST :: [[Block]] -> State WriterState Doc
+notesToRST :: PandocMonad m => [[Block]] -> RST m Doc
notesToRST notes =
- mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>=
+ zipWithM noteToRST [1..] notes >>=
return . vsep
-- | Return RST representation of a note.
-noteToRST :: Int -> [Block] -> State WriterState Doc
+noteToRST :: PandocMonad m => Int -> [Block] -> RST m Doc
noteToRST num note = do
contents <- blockListToRST note
let marker = ".. [" <> text (show num) <> "]"
return $ nowrap $ marker $$ nest 3 contents
-- | Return RST representation of picture reference table.
-pictRefsToRST :: [([Inline], (Attr, String, String, Maybe String))]
- -> State WriterState Doc
+pictRefsToRST :: PandocMonad m
+ => [([Inline], (Attr, String, String, Maybe String))]
+ -> RST m Doc
pictRefsToRST refs = mapM pictToRST refs >>= return . vcat
-- | Return RST representation of a picture substitution reference.
-pictToRST :: ([Inline], (Attr, String, String, Maybe String))
- -> State WriterState Doc
+pictToRST :: PandocMonad m
+ => ([Inline], (Attr, String, String, Maybe String))
+ -> RST m Doc
pictToRST (label, (attr, src, _, mbtarget)) = do
label' <- inlineListToRST label
dims <- imageDimsToRST attr
@@ -160,10 +166,27 @@ pictToRST (label, (attr, src, _, mbtarget)) = do
Just t -> " :target: " <> text t
-- | Escape special characters for RST.
-escapeString :: String -> String
-escapeString = escapeStringUsing (backslashEscapes "`\\|*_")
+escapeString :: WriterOptions -> String -> String
+escapeString = escapeString' True
+ where
+ escapeString' _ _ [] = []
+ escapeString' firstChar opts (c:cs) =
+ case c of
+ _ | c `elem` ['\\','`','*','_','|'] &&
+ (firstChar || null cs) -> '\\':c:escapeString' False opts cs
+ '\'' | isEnabled Ext_smart opts -> '\\':'\'':escapeString' False opts cs
+ '"' | isEnabled Ext_smart opts -> '\\':'"':escapeString' False opts cs
+ '-' | isEnabled Ext_smart opts ->
+ case cs of
+ '-':_ -> '\\':'-':escapeString' False opts cs
+ _ -> '-':escapeString' False opts cs
+ '.' | isEnabled Ext_smart opts ->
+ case cs of
+ '.':'.':rest -> '\\':'.':'.':'.':escapeString' False opts rest
+ _ -> '.':escapeString' False opts cs
+ _ -> c : escapeString' False opts cs
-titleToRST :: [Inline] -> [Inline] -> State WriterState Doc
+titleToRST :: PandocMonad m => [Inline] -> [Inline] -> RST m Doc
titleToRST [] _ = return empty
titleToRST tit subtit = do
title <- inlineListToRST tit
@@ -179,8 +202,9 @@ bordered contents c =
border = text (replicate len c)
-- | Convert Pandoc block element to RST.
-blockToRST :: Block -- ^ Block element
- -> State WriterState Doc
+blockToRST :: PandocMonad m
+ => Block -- ^ Block element
+ -> RST m Doc
blockToRST Null = return empty
blockToRST (Div attr bs) = do
contents <- blockListToRST bs
@@ -200,7 +224,7 @@ blockToRST (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
else ":figclass: " <> text (unwords cls)
return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline
blockToRST (Para inlines)
- | LineBreak `elem` inlines = do -- use line block if LineBreaks
+ | LineBreak `elem` inlines =
linesToLineBlock $ splitBy (==LineBreak) inlines
| otherwise = do
contents <- inlineListToRST inlines
@@ -211,17 +235,22 @@ blockToRST (RawBlock f@(Format f') str)
| f == "rst" = return $ text str
| otherwise = return $ blankline <> ".. raw:: " <>
text (map toLower f') $+$
- (nest 3 $ text str) $$ blankline
+ nest 3 (text str) $$ blankline
blockToRST HorizontalRule =
return $ blankline $$ "--------------" $$ blankline
blockToRST (Header level (name,classes,_) inlines) = do
contents <- inlineListToRST inlines
+ -- we calculate the id that would be used by auto_identifiers
+ -- so we know whether to print an explicit identifier
+ let autoId = uniqueIdent inlines mempty
isTopLevel <- gets stTopLevel
if isTopLevel
then do
let headerChar = if level > 5 then ' ' else "=-~^'" !! (level - 1)
let border = text $ replicate (offset contents) headerChar
- return $ nowrap $ contents $$ border $$ blankline
+ let anchor | null name || name == autoId = empty
+ | otherwise = ".. _" <> text name <> ":" $$ blankline
+ return $ nowrap $ anchor $$ contents $$ border $$ blankline
else do
let rub = "rubric:: " <> contents
let name' | null name = empty
@@ -230,7 +259,7 @@ blockToRST (Header level (name,classes,_) inlines) = do
| otherwise = ":class: " <> text (unwords classes)
return $ nowrap $ hang 3 ".. " (rub $$ name' $$ cls) $$ blankline
blockToRST (CodeBlock (_,classes,kvs) str) = do
- opts <- stOptions <$> get
+ opts <- gets stOptions
let tabstop = writerTabStop opts
let startnum = maybe "" (\x -> " " <> text x) $ lookup "startFrom" kvs
let numberlines = if "numberLines" `elem` classes
@@ -246,59 +275,38 @@ blockToRST (CodeBlock (_,classes,kvs) str) = do
(lang:_) -> (".. code:: " <> text lang) $$ numberlines)
$+$ nest tabstop (text str) $$ blankline
blockToRST (BlockQuote blocks) = do
- tabstop <- get >>= (return . writerTabStop . stOptions)
+ tabstop <- gets $ writerTabStop . stOptions
contents <- blockListToRST blocks
- return $ (nest tabstop contents) <> blankline
-blockToRST (Table caption _ widths headers rows) = do
+ return $ nest tabstop contents <> blankline
+blockToRST (Table caption aligns widths headers rows) = do
caption' <- inlineListToRST caption
- let caption'' = if null caption
- then empty
- else blankline <> text "Table: " <> caption'
- headers' <- mapM blockListToRST headers
- rawRows <- mapM (mapM blockListToRST) rows
- -- let isSimpleCell [Plain _] = True
- -- isSimpleCell [Para _] = True
- -- isSimpleCell [] = True
- -- isSimpleCell _ = False
- -- let isSimple = all (==0) widths && all (all isSimpleCell) rows
- let numChars = maximum . map offset
- opts <- get >>= return . stOptions
- let widthsInChars =
- if all (== 0) widths
- then map ((+2) . numChars) $ transpose (headers' : rawRows)
- else map (floor . (fromIntegral (writerColumns opts) *)) widths
- let hpipeBlocks blocks = hcat [beg, middle, end]
- where h = height (hcat blocks)
- sep' = lblock 3 $ vcat (map text $ replicate h " | ")
- beg = lblock 2 $ vcat (map text $ replicate h "| ")
- end = lblock 2 $ vcat (map text $ replicate h " |")
- middle = hcat $ intersperse sep' blocks
- let makeRow = hpipeBlocks . zipWith lblock widthsInChars
- let head' = makeRow headers'
- let rows' = map makeRow rawRows
- let border ch = char '+' <> char ch <>
- (hcat $ intersperse (char ch <> char '+' <> char ch) $
- map (\l -> text $ replicate l ch) widthsInChars) <>
- char ch <> char '+'
- let body = vcat $ intersperse (border '-') rows'
- let head'' = if all null headers
- then empty
- else head' $$ border '='
- return $ border '-' $$ head'' $$ body $$ border '-' $$ caption'' $$ blankline
+ let blocksToDoc opts bs = do
+ oldOpts <- gets stOptions
+ modify $ \st -> st{ stOptions = opts }
+ result <- blockListToRST bs
+ modify $ \st -> st{ stOptions = oldOpts }
+ return result
+ opts <- gets stOptions
+ tbl <- gridTable opts blocksToDoc (all null headers)
+ (map (const AlignDefault) aligns) widths
+ headers rows
+ return $ if null caption
+ then tbl $$ blankline
+ else (".. table:: " <> caption') $$ blankline $$ nest 3 tbl $$
+ blankline
blockToRST (BulletList items) = do
contents <- mapM bulletListItemToRST items
-- ensure that sublists have preceding blank line
return $ blankline $$ chomp (vcat contents) $$ blankline
blockToRST (OrderedList (start, style', delim) items) = do
let markers = if start == 1 && style' == DefaultStyle && delim == DefaultDelim
- then take (length items) $ repeat "#."
+ then replicate (length items) "#."
else take (length items) $ orderedListMarkers
(start, style', delim)
let maxMarkerLength = maximum $ map length markers
let markers' = map (\m -> let s = maxMarkerLength - length m
in m ++ replicate s ' ') markers
- contents <- mapM (\(item, num) -> orderedListItemToRST item num) $
- zip markers' items
+ contents <- zipWithM orderedListItemToRST markers' items
-- ensure that sublists have preceding blank line
return $ blankline $$ chomp (vcat contents) $$ blankline
blockToRST (DefinitionList items) = do
@@ -307,51 +315,69 @@ blockToRST (DefinitionList items) = do
return $ blankline $$ chomp (vcat contents) $$ blankline
-- | Convert bullet list item (list of blocks) to RST.
-bulletListItemToRST :: [Block] -> State WriterState Doc
+bulletListItemToRST :: PandocMonad m => [Block] -> RST m Doc
bulletListItemToRST items = do
contents <- blockListToRST items
return $ hang 3 "- " $ contents <> cr
-- | Convert ordered list item (a list of blocks) to RST.
-orderedListItemToRST :: String -- ^ marker for list item
+orderedListItemToRST :: PandocMonad m
+ => String -- ^ marker for list item
-> [Block] -- ^ list item (list of blocks)
- -> State WriterState Doc
+ -> RST m Doc
orderedListItemToRST marker items = do
contents <- blockListToRST items
let marker' = marker ++ " "
return $ hang (length marker') (text marker') $ contents <> cr
-- | Convert defintion list item (label, list of blocks) to RST.
-definitionListItemToRST :: ([Inline], [[Block]]) -> State WriterState Doc
+definitionListItemToRST :: PandocMonad m => ([Inline], [[Block]]) -> RST m Doc
definitionListItemToRST (label, defs) = do
label' <- inlineListToRST label
contents <- liftM vcat $ mapM blockListToRST defs
- tabstop <- get >>= (return . writerTabStop . stOptions)
- return $ label' $$ nest tabstop (nestle contents <> cr)
+ tabstop <- gets $ writerTabStop . stOptions
+ return $ nowrap label' $$ nest tabstop (nestle contents <> cr)
-- | Format a list of lines as line block.
-linesToLineBlock :: [[Inline]] -> State WriterState Doc
+linesToLineBlock :: PandocMonad m => [[Inline]] -> RST m Doc
linesToLineBlock inlineLines = do
lns <- mapM inlineListToRST inlineLines
- return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline
+ return $
+ vcat (map (hang 2 (text "| ")) lns) <> blankline
-- | Convert list of Pandoc block elements to RST.
-blockListToRST' :: Bool
+blockListToRST' :: PandocMonad m
+ => Bool
-> [Block] -- ^ List of block elements
- -> State WriterState Doc
+ -> RST m Doc
blockListToRST' topLevel blocks = do
+ -- insert comment between list and quoted blocks, see #4248 and #3675
+ let fixBlocks (b1:b2@(BlockQuote _):bs)
+ | toClose b1 = b1 : commentSep : b2 : fixBlocks bs
+ where
+ toClose Plain{} = False
+ toClose Header{} = False
+ toClose LineBlock{} = False
+ toClose HorizontalRule = False
+ toClose (Para [Image _ _ (_,'f':'i':'g':':':_)]) = True
+ toClose Para{} = False
+ toClose _ = True
+ commentSep = RawBlock "rst" "..\n\n"
+ fixBlocks (b:bs) = b : fixBlocks bs
+ fixBlocks [] = []
tl <- gets stTopLevel
modify (\s->s{stTopLevel=topLevel})
- res <- vcat `fmap` mapM blockToRST blocks
+ res <- vcat `fmap` mapM blockToRST (fixBlocks blocks)
modify (\s->s{stTopLevel=tl})
return res
-blockListToRST :: [Block] -- ^ List of block elements
- -> State WriterState Doc
+blockListToRST :: PandocMonad m
+ => [Block] -- ^ List of block elements
+ -> RST m Doc
blockListToRST = blockListToRST' False
-- | Convert list of Pandoc inline elements to RST.
-inlineListToRST :: [Inline] -> State WriterState Doc
+inlineListToRST :: PandocMonad m => [Inline] -> RST m Doc
inlineListToRST lst =
mapM inlineToRST (removeSpaceAfterDisplayMath $ insertBS lst) >>=
return . hcat
@@ -362,7 +388,7 @@ inlineListToRST lst =
removeSpaceAfterDisplayMath [] = []
insertBS :: [Inline] -> [Inline] -- insert '\ ' where needed
insertBS (x:y:z:zs)
- | isComplex y && (surroundComplex x z) =
+ | isComplex y && surroundComplex x z =
x : y : insertBS (z : zs)
insertBS (x:y:zs)
| isComplex x && not (okAfterComplex y) =
@@ -396,23 +422,28 @@ inlineListToRST lst =
okBeforeComplex (Str (c:_)) = isSpace c || c `elem` ("-:/'\"<([{–—" :: String)
okBeforeComplex _ = False
isComplex :: Inline -> Bool
- isComplex (Emph _) = True
- isComplex (Strong _) = True
- isComplex (SmallCaps _) = True
- isComplex (Strikeout _) = True
+ isComplex (Emph _) = True
+ isComplex (Strong _) = True
+ isComplex (SmallCaps _) = True
+ isComplex (Strikeout _) = True
isComplex (Superscript _) = True
- isComplex (Subscript _) = True
- isComplex (Link _ _ _) = True
- isComplex (Image _ _ _) = True
- isComplex (Code _ _) = True
- isComplex (Math _ _) = True
- isComplex (Cite _ (x:_)) = isComplex x
- isComplex (Span _ (x:_)) = isComplex x
- isComplex _ = False
+ isComplex (Subscript _) = True
+ isComplex Link{} = True
+ isComplex Image{} = True
+ isComplex (Code _ _) = True
+ isComplex (Math _ _) = True
+ isComplex (Cite _ (x:_)) = isComplex x
+ isComplex (Span _ (x:_)) = isComplex x
+ isComplex _ = False
-- | Convert Pandoc inline element to RST.
-inlineToRST :: Inline -> State WriterState Doc
-inlineToRST (Span _ ils) = inlineListToRST ils
+inlineToRST :: PandocMonad m => Inline -> RST m Doc
+inlineToRST (Span (_,_,kvs) ils) = do
+ contents <- inlineListToRST ils
+ return $
+ case lookup "role" kvs of
+ Just role -> ":" <> text role <> ":`" <> contents <> "`"
+ Nothing -> contents
inlineToRST (Emph lst) = do
contents <- inlineListToRST lst
return $ "*" <> contents <> "*"
@@ -431,14 +462,33 @@ inlineToRST (Subscript lst) = do
inlineToRST (SmallCaps lst) = inlineListToRST lst
inlineToRST (Quoted SingleQuote lst) = do
contents <- inlineListToRST lst
- return $ "‘" <> contents <> "’"
+ opts <- gets stOptions
+ if isEnabled Ext_smart opts
+ then return $ "'" <> contents <> "'"
+ else return $ "‘" <> contents <> "’"
inlineToRST (Quoted DoubleQuote lst) = do
contents <- inlineListToRST lst
- return $ "“" <> contents <> "”"
+ opts <- gets stOptions
+ if isEnabled Ext_smart opts
+ then return $ "\"" <> contents <> "\""
+ else return $ "“" <> contents <> "”"
inlineToRST (Cite _ lst) =
inlineListToRST lst
-inlineToRST (Code _ str) = return $ "``" <> text str <> "``"
-inlineToRST (Str str) = return $ text $ escapeString str
+inlineToRST (Code _ str) = do
+ opts <- gets stOptions
+ -- we trim the string because the delimiters must adjoin a
+ -- non-space character; see #3496
+ -- we use :literal: when the code contains backticks, since
+ -- :literal: allows backslash-escapes; see #3974
+ return $ if '`' `elem` str
+ then ":literal:`" <> text (escapeString opts (trim str)) <> "`"
+ else "``" <> text (trim str) <> "``"
+inlineToRST (Str str) = do
+ opts <- gets stOptions
+ return $ text $
+ (if isEnabled Ext_smart opts
+ then unsmartify opts
+ else id) $ escapeString opts str
inlineToRST (Math t str) = do
modify $ \st -> st{ stHasMath = True }
return $ if t == InlineMath
@@ -447,20 +497,20 @@ inlineToRST (Math t str) = do
then blankline $$ ".. math::" $$
blankline $$ nest 3 (text str) $$ blankline
else blankline $$ (".. math:: " <> text str) $$ blankline
-inlineToRST (RawInline f x)
+inlineToRST il@(RawInline f x)
| f == "rst" = return $ text x
| f == "latex" || f == "tex" = do
modify $ \st -> st{ stHasRawTeX = True }
return $ ":raw-latex:`" <> text x <> "`"
- | otherwise = return empty
-inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para)
+ | otherwise = empty <$ report (InlineNotRendered il)
+inlineToRST LineBreak = return cr -- there's no line break in RST (see Para)
inlineToRST Space = return space
inlineToRST SoftBreak = do
- wrapText <- gets (writerWrapText . stOptions)
+ wrapText <- gets $ writerWrapText . stOptions
case wrapText of
- WrapPreserve -> return cr
- WrapAuto -> return space
- WrapNone -> return space
+ WrapPreserve -> return cr
+ WrapAuto -> return space
+ WrapNone -> return space
-- autolink
inlineToRST (Link _ [Str str] (src, _))
| isURI src &&
@@ -473,15 +523,15 @@ inlineToRST (Link _ [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do
label <- registerImage attr alt (imgsrc,imgtit) (Just src)
return $ "|" <> label <> "|"
inlineToRST (Link _ txt (src, tit)) = do
- useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions
- linktext <- inlineListToRST $ normalizeSpaces txt
+ useReferenceLinks <- gets $ writerReferenceLinks . stOptions
+ linktext <- inlineListToRST $ B.toList . B.trimInlines . B.fromList $ txt
if useReferenceLinks
- then do refs <- get >>= return . stLinks
+ then do refs <- gets stLinks
case lookup txt refs of
Just (src',tit') ->
if src == src' && tit == tit'
then return $ "`" <> linktext <> "`_"
- else do -- duplicate label, use non-reference link
+ else
return $ "`" <> linktext <> " <" <> text src <> ">`__"
Nothing -> do
modify $ \st -> st { stLinks = (txt,(src,tit)):refs }
@@ -494,12 +544,12 @@ inlineToRST (Note contents) = do
-- add to notes in state
notes <- gets stNotes
modify $ \st -> st { stNotes = contents:notes }
- let ref = show $ (length notes) + 1
+ let ref = show $ length notes + 1
return $ " [" <> text ref <> "]_"
-registerImage :: Attr -> [Inline] -> Target -> Maybe String -> State WriterState Doc
+registerImage :: PandocMonad m => Attr -> [Inline] -> Target -> Maybe String -> RST m Doc
registerImage attr alt (src,tit) mbtarget = do
- pics <- get >>= return . stImages
+ pics <- gets stImages
txt <- case lookup alt pics of
Just (a,s,t,mbt) | (a,s,t,mbt) == (attr,src,tit,mbtarget)
-> return alt
@@ -512,14 +562,14 @@ registerImage attr alt (src,tit) mbtarget = do
return alt'
inlineListToRST txt
-imageDimsToRST :: Attr -> State WriterState Doc
+imageDimsToRST :: PandocMonad m => Attr -> RST m Doc
imageDimsToRST attr = do
let (ident, _, _) = attr
name = if null ident
then empty
else ":name: " <> text ident
showDim dir = let cols d = ":" <> text (show dir) <> ": " <> text (show d)
- in case (dimension dir attr) of
+ in case dimension dir attr of
Just (Percent a) ->
case dir of
Height -> empty