diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 6 |
3 files changed, 9 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 0adc190c3..f27b02f25 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -141,6 +141,12 @@ metaFromDefList ds meta = adjustAuthors $ foldr f meta ds splitAuthors x = x splitAuthors' = map normalizeSpaces . splitOnSemi . concatMap factorSemi + normalizeSpaces = reverse . dropWhile isSp . reverse . + dropWhile isSp + isSp Space = True + isSp SoftBreak = True + isSp LineBreak = True + isSp _ = False splitOnSemi = splitBy (==Str ";") factorSemi (Str []) = [] factorSemi (Str s) = case break (==';') s of diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 2eacbcc1c..3b9ae7501 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -53,7 +53,6 @@ module Text.Pandoc.Shared ( normalizeDate, -- * Pandoc block and inline list processing orderedListMarkers, - normalizeSpaces, extractSpaces, removeFormatting, deNote, @@ -354,25 +353,6 @@ orderedListMarkers (start, numstyle, numdelim) = TwoParens -> "(" ++ str ++ ")" in map inDelim nums --- | Normalize a list of inline elements: remove leading and trailing --- @Space@, @LineBreak@, and @SoftBreak@ elements, collapse double --- @Space@s into singles, and remove empty @Str@ elements. -normalizeSpaces :: [Inline] -> [Inline] -normalizeSpaces = cleanup . dropWhile isSpaceOrEmpty - where cleanup [] = [] - cleanup (Space:rest) = case dropWhile isSpaceOrEmpty rest of - [] -> [] - (x:xs) -> Space : x : cleanup xs - cleanup ((Str ""):rest) = cleanup rest - cleanup (x:rest) = x : cleanup rest - -isSpaceOrEmpty :: Inline -> Bool -isSpaceOrEmpty Space = True -isSpaceOrEmpty SoftBreak = True -isSpaceOrEmpty LineBreak = True -isSpaceOrEmpty (Str "") = True -isSpaceOrEmpty _ = False - -- | Extract the leading and trailing spaces from inside an inline element -- and place them outside the element. SoftBreaks count as Spaces for -- these purposes. diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 2657afa2a..496350024 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -36,7 +36,7 @@ import Data.Char (isSpace, toLower) import Data.List (intersperse, isPrefixOf, stripPrefix, transpose) import Data.Maybe (fromMaybe) import Network.URI (isURI) -import Text.Pandoc.Builder (deleteMeta) +import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.ImageSize @@ -81,7 +81,7 @@ pandocToRST (Pandoc meta blocks) = do metadata <- metaToJSON opts (fmap (render colwidth) . blockListToRST) (fmap (trimr . render colwidth) . inlineListToRST) - $ deleteMeta "title" $ deleteMeta "subtitle" meta + $ B.deleteMeta "title" $ B.deleteMeta "subtitle" meta body <- blockListToRST' True $ case writerTemplate opts of Just _ -> normalizeHeadings 1 blocks Nothing -> blocks @@ -504,7 +504,7 @@ inlineToRST (Link _ [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do return $ "|" <> label <> "|" inlineToRST (Link _ txt (src, tit)) = do useReferenceLinks <- gets $ writerReferenceLinks . stOptions - linktext <- inlineListToRST $ normalizeSpaces txt + linktext <- inlineListToRST $ B.toList . B.trimInlines . B.fromList $ txt if useReferenceLinks then do refs <- gets stLinks case lookup txt refs of |