aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2021-09-27 14:28:26 -0700
committerJohn MacFarlane <[email protected]>2021-09-29 08:37:08 -0700
commit88164609ce5b1f6a593e4621d9513a839bf56b85 (patch)
tree246031ffec901e41868501f5f235a681cdd53e17
parent11b8f67d16995f23fdbac55b8ec53f3177f4e01f (diff)
More.
-rw-r--r--src/Text/Pandoc/Citeproc/BibTeX.hs5
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs3
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs6
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs10
4 files changed, 11 insertions, 13 deletions
diff --git a/src/Text/Pandoc/Citeproc/BibTeX.hs b/src/Text/Pandoc/Citeproc/BibTeX.hs
index 0fafea0ea..b854e82c0 100644
--- a/src/Text/Pandoc/Citeproc/BibTeX.hs
+++ b/src/Text/Pandoc/Citeproc/BibTeX.hs
@@ -1174,7 +1174,8 @@ toName _ [Span ("",[],[]) ils] = -- corporate author
-- extended BibLaTeX name format - see #266
toName _ ils@(Str ys:_) | T.any (== '=') ys = do
let commaParts = splitWhen (== Str ",")
- . splitStrWhen (\c -> c == ',' || c == '=' || c == '\160')
+ . splitStrWhen (\c -> c == ',' || c == '=' || c == '\160' ||
+ c == ' ')
$ ils
let addPart ag (Str "given" : Str "=" : xs) =
ag{ nameGiven = case nameGiven ag of
@@ -1208,7 +1209,7 @@ toName opts ils = do
let useprefix = optionSet "useprefix" opts
let usecomma = optionSet "juniorcomma" opts
let bibtex = optionSet "bibtex" opts
- let words' = wordsBy (\x -> x == Space || x == Str "\160")
+ let words' = wordsBy (\x -> x == ' ' || x == Str "\160")
let commaParts = map words' $ splitWhen (== Str ",")
$ splitStrWhen
(\c -> c == ',' || c == '\160') ils
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 825e4a2eb..39b676005 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -199,7 +199,7 @@ block = do
para :: PandocMonad m => MWParser m Blocks
para = do
contents <- trimInlines . mconcat <$> many1 inline
- if F.all (==Space) contents
+ if null contents
then return mempty
else return $ B.para contents
@@ -389,7 +389,6 @@ preformatted = try $ do
encode :: Inlines -> Inlines
encode = B.fromList . normalizeCode . B.toList . walk strToCode
where strToCode (Str s) = Code ("",[],[]) s
- strToCode Space = Code ("",[],[]) " "
strToCode x = x
normalizeCode [] = []
normalizeCode (Code a1 x : Code a2 y : zs) | a1 == a2 =
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 2ec97d903..12012a8bc 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -900,9 +900,9 @@ listItem parseIndentedMarker = try . withContext ListItemState $ do
prependInlines :: Inline -> Blocks -> Blocks
prependInlines inlns = B.fromList . prepend . B.toList
where
- prepend (Plain is : bs) = Plain (inlns : Space : is) : bs
- prepend (Para is : bs) = Para (inlns : Space : is) : bs
- prepend bs = Plain [inlns, Space] : bs
+ prepend (Plain is : bs) = Plain (inlns : Str " " : is) : bs
+ prepend (Para is : bs) = Para (inlns : Str " " : is) : bs
+ prepend bs = Plain [inlns, Str " "] : bs
-- continuation of a list item - indented and separated by blankline or endline.
-- Note: nested lists are parsed as continuations.
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index 276d28aaa..aa283fd2b 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -17,7 +17,6 @@ module Text.Pandoc.Readers.TWiki ( readTWiki
import Control.Monad
import Control.Monad.Except (throwError)
import Data.Char (isAlphaNum)
-import qualified Data.Foldable as F
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
@@ -285,16 +284,15 @@ noautolink = do
parseContent = parseFromString' $ many block
para :: PandocMonad m => TWParser m B.Blocks
-para = result . mconcat <$> many1Till inline endOfParaElement
+para = result . B.trimInlines . mconcat <$> many1Till inline endOfParaElement
where
endOfParaElement = lookAhead $ endOfInput <|> endOfPara <|> newBlockElement
endOfInput = try $ skipMany blankline >> skipSpaces >> eof
endOfPara = try $ blankline >> skipMany1 blankline
newBlockElement = try $ blankline >> void blockElements
- result content = if F.all (==Space) content
- then mempty
- else B.para $ B.trimInlines content
-
+ result content = if null content
+ then mempty
+ else B.para content
--
-- inline parsers