aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2021-09-27 09:39:53 -0700
committerJohn MacFarlane <[email protected]>2021-09-29 08:37:08 -0700
commit64395389a4e1e64df915be95e97478da91c93f43 (patch)
tree65ee155cace3d73dd3856295354af1668e16611b
parent3fe4b44d852a89327fc9c4a57facfd096eee2613 (diff)
More.
-rw-r--r--src/Text/Pandoc/Citeproc/Locator.hs4
-rw-r--r--src/Text/Pandoc/Parsing.hs4
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docx/Table.hs4
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Citation.hs8
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs12
-rw-r--r--src/Text/Pandoc/Writers/Markdown/Inline.hs10
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs29
8 files changed, 52 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Citeproc/Locator.hs b/src/Text/Pandoc/Citeproc/Locator.hs
index f8931d7b5..18c27015b 100644
--- a/src/Text/Pandoc/Citeproc/Locator.hs
+++ b/src/Text/Pandoc/Citeproc/Locator.hs
@@ -47,10 +47,10 @@ pLocatorWords locMap = do
maybeAddComma :: [Inline] -> [Inline]
maybeAddComma [] = []
-maybeAddComma ils@(Space : _) = ils
+maybeAddComma ils@(SoftBreak : _) = ils
maybeAddComma ils@(Str t : _)
| Just (c, _) <- T.uncons t
- , isPunctuation c = ils
+ , isPunctuation c || c == ' ' || c == '\t' = ils
maybeAddComma ils = Str "," : Space : ils
pLocatorDelimited :: LocatorMap -> LocatorParser (Text, Text)
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index cfda4bad2..6f13a1d6d 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -1199,10 +1199,10 @@ gridTableRow blocks indices = do
removeOneLeadingSpace :: [Text] -> [Text]
removeOneLeadingSpace xs =
- if all startsWithSpace xs
+ if all textStartsWithSpace xs
then map (T.drop 1) xs
else xs
- where startsWithSpace t = case T.uncons t of
+ where textStartsWithSpace t = case T.uncons t of
Nothing -> True
Just (c, _) -> c == ' '
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 5520d039f..a163abfe9 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -570,7 +570,7 @@ read_text_seq = matchingElement NsText "sequence"
read_spaces :: InlineMatcher
read_spaces = matchingElement NsText "s" (
readAttrWithDefault NsText "c" 1 -- how many spaces?
- >>^ fromList.(`replicate` Space)
+ >>^ fromList . (:[]) . Str . (`T.replicate` ' ')
)
--
read_line_break :: InlineMatcher
diff --git a/src/Text/Pandoc/Writers/Docx/Table.hs b/src/Text/Pandoc/Writers/Docx/Table.hs
index e23856f28..14ce990de 100644
--- a/src/Text/Pandoc/Writers/Docx/Table.hs
+++ b/src/Text/Pandoc/Writers/Docx/Table.hs
@@ -98,8 +98,8 @@ tableToOpenXML opts blocksToOpenXML gridTable = do
addLabel :: Text -> Text -> Int -> [Block] -> [Block]
addLabel tableid tablename tablenum bs =
case bs of
- (Para ils : rest) -> Para (label : Space : ils) : rest
- (Plain ils : rest) -> Plain (label : Space : ils) : rest
+ (Para ils : rest) -> Para (label : Str " " : ils) : rest
+ (Plain ils : rest) -> Plain (label : Str " " : ils) : rest
_ -> Para [label] : bs
where
label = Span (tableid,[],[])
diff --git a/src/Text/Pandoc/Writers/LaTeX/Citation.hs b/src/Text/Pandoc/Writers/LaTeX/Citation.hs
index f48a43d7a..ba893b1b5 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Citation.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Citation.hs
@@ -109,7 +109,13 @@ citeArgumentsList inlineListToLaTeX (CiteGroup pfxs sfxs ids) = do
(Str t : r) -> case T.uncons t of
Just (x, xs)
| T.null xs
- , isPunctuation x -> dropWhile (== Space) r
+ , isPunctuation x ->
+ case r of
+ (Str t : rs) ->
+ case T.dropWhile (== ' ') t of
+ t' | T.null t' -> rs
+ | otherwise -> Str t' : rs
+ _ -> r
| isPunctuation x -> Str xs : r
_ -> sfxs
_ -> sfxs
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index fda2bbcef..b188d3fae 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -346,9 +346,6 @@ blockToMarkdown' opts (Plain inlines) = do
let escapeMarker = T.concatMap $ \x -> if x `elemText` ".()"
then T.pack ['\\', x]
else T.singleton x
- let startsWithSpace (Space:_) = True
- startsWithSpace (SoftBreak:_) = True
- startsWithSpace _ = False
let inlines' =
if variant == PlainText
then inlines
@@ -821,3 +818,12 @@ lineBreakToSpace :: Inline -> Inline
lineBreakToSpace LineBreak = Space
lineBreakToSpace SoftBreak = Space
lineBreakToSpace x = x
+
+-- | Starts with space or soft break.
+startsWithSpace :: [Inline] -> Bool
+startsWithSpace (Str t : _) =
+ case T.uncons t of
+ Just (c,_) -> c == ' ' || c == '\t' || c == '\r' || c == '\n'
+ _ -> False
+startsWithSpace (SoftBreak : _) = True
+startsWithSpace _ = False
diff --git a/src/Text/Pandoc/Writers/Markdown/Inline.hs b/src/Text/Pandoc/Writers/Markdown/Inline.hs
index 31c816e36..0c4ca57e2 100644
--- a/src/Text/Pandoc/Writers/Markdown/Inline.hs
+++ b/src/Text/Pandoc/Writers/Markdown/Inline.hs
@@ -46,10 +46,10 @@ import Text.Pandoc.Writers.Markdown.Types (MarkdownVariant(..),
escapeText :: WriterOptions -> Text -> Text
escapeText opts = T.pack . go . T.unpack
where
- startsWithSpace (' ':_) = True
- startsWithSpace ('\t':_) = True
- startsWithSpace [] = True
- startsWithSpace _ = False
+ stringStartsWithSpace (' ':_) = True
+ stringStartsWithSpace ('\t':_) = True
+ stringStartsWithSpace [] = True
+ stringStartsWithSpace _ = False
go [] = []
go (c:cs) =
case c of
@@ -66,7 +66,7 @@ escapeText opts = T.pack . go . T.unpack
-> '\\':'@':go cs
_ -> '@':go cs
'#' | isEnabled Ext_space_in_atx_header opts
- , startsWithSpace cs
+ , stringStartsWithSpace cs
-> '\\':'#':go cs
_ | c `elem` ['\\','`','*','_','[',']'] ->
'\\':c:go cs
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index 6db06408f..b930d2d73 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -38,7 +38,7 @@ module Text.Pandoc.Writers.Shared (
, toLegacyTable
)
where
-import Safe (lastMay)
+import Safe (lastMay, initSafe)
import qualified Data.ByteString.Lazy as BL
import Data.Maybe (fromMaybe, isNothing)
import Control.Monad (zipWithM)
@@ -184,10 +184,29 @@ isDisplayMath _ = False
-- | Remove leading and trailing spaces and 'SoftBreak' elements.
stripLeadingTrailingSpace :: [Inline] -> [Inline]
-stripLeadingTrailingSpace = go . reverse . go . reverse
- where go (Space:xs) = xs
- go (SoftBreak:xs) = xs
- go xs = xs
+stripLeadingTrailingSpace = stripLeadingSpace . stripTrailingSpace
+ where
+ isWS ' ' = True
+ isWS '\t' = True
+ isWS '\n' = True
+ isWS '\r' = True
+ isWS _ = False
+ stripTrailingSpace ils =
+ case lastMay ils of
+ Just SoftBreak -> stripTrailingSpace $ initSafe ils
+ Just (Str t) ->
+ case T.dropWhileEnd isWS t of
+ t' | T.null t' -> stripTrailingSpace $ initSafe ils
+ | otherwise -> initSafe ils ++ [Str t']
+ _ -> ils
+ stripLeadingSpace ils =
+ case ils of
+ (SoftBreak:ils') -> stripLeadingSpace ils'
+ (Str t:ils') ->
+ case T.dropWhile isWS t of
+ t' | T.null t' -> stripLeadingSpace ils'
+ | otherwise -> Str t' : ils'
+ _ -> ils
-- | Put display math in its own block (for ODT/DOCX).
fixDisplayMath :: Block -> Block