aboutsummaryrefslogtreecommitdiff
path: root/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'Text/Pandoc/Readers')
-rw-r--r--Text/Pandoc/Readers/HTML.hs6
-rw-r--r--Text/Pandoc/Readers/Markdown.hs12
-rw-r--r--Text/Pandoc/Readers/RST.hs6
3 files changed, 12 insertions, 12 deletions
diff --git a/Text/Pandoc/Readers/HTML.hs b/Text/Pandoc/Readers/HTML.hs
index 72e54ed23..a9025f0d2 100644
--- a/Text/Pandoc/Readers/HTML.hs
+++ b/Text/Pandoc/Readers/HTML.hs
@@ -46,7 +46,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
import Data.Maybe ( fromMaybe )
-import Data.List ( takeWhile, dropWhile, isPrefixOf, isSuffixOf )
+import Data.List ( takeWhile, dropWhile, isPrefixOf, isSuffixOf, intercalate )
import Data.Char ( toLower, isAlphaNum )
import Network.URI ( parseURIReference, URI (..) )
@@ -534,7 +534,7 @@ definitionListItem :: GenParser Char ParserState ([Inline], [Block])
definitionListItem = try $ do
terms <- sepEndBy1 (inlinesIn "dt") spaces
defs <- sepEndBy1 (blocksIn "dd") spaces
- let term = joinWithSep [LineBreak] terms
+ let term = intercalate [LineBreak] terms
return (term, concat defs)
--
@@ -580,7 +580,7 @@ code = try $ do
-- remove internal line breaks, leading and trailing space,
-- and decode character references
return $ Code $ decodeCharacterReferences $ removeLeadingTrailingSpace $
- joinWithSep " " $ lines result
+ intercalate " " $ lines result
rawHtmlInline :: GenParser Char ParserState Inline
rawHtmlInline = do
diff --git a/Text/Pandoc/Readers/Markdown.hs b/Text/Pandoc/Readers/Markdown.hs
index 88ab38fcf..e2a98dd6d 100644
--- a/Text/Pandoc/Readers/Markdown.hs
+++ b/Text/Pandoc/Readers/Markdown.hs
@@ -32,7 +32,7 @@ module Text.Pandoc.Readers.Markdown (
readMarkdown
) where
-import Data.List ( transpose, isPrefixOf, isSuffixOf, lookup, sortBy, findIndex )
+import Data.List ( transpose, isPrefixOf, isSuffixOf, lookup, sortBy, findIndex, intercalate )
import Data.Ord ( comparing )
import Data.Char ( isAlphaNum, isAlpha, isLower, isDigit )
import Data.Maybe
@@ -234,7 +234,7 @@ noteBlock = try $ do
optional blanklines
endPos <- getPosition
-- parse the extracted text, which may contain various block elements:
- contents <- parseFromString parseBlocks $ (joinWithSep "\n" raw) ++ "\n\n"
+ contents <- parseFromString parseBlocks $ (intercalate "\n" raw) ++ "\n\n"
let newnote = (ref, contents)
st <- getState
let oldnotes = stateNotes st
@@ -381,7 +381,7 @@ codeBlockDelimited = try $ do
(size, attr) <- codeBlockDelimiter Nothing
contents <- manyTill anyLine (codeBlockDelimiter (Just size))
blanklines
- return $ CodeBlock attr $ joinWithSep "\n" contents
+ return $ CodeBlock attr $ intercalate "\n" contents
codeBlockIndented :: GenParser Char ParserState Block
codeBlockIndented = do
@@ -414,7 +414,7 @@ blockQuote :: GenParser Char ParserState Block
blockQuote = do
raw <- emailBlockQuote
-- parse the extracted block, which may contain various block elements:
- contents <- parseFromString parseBlocks $ (joinWithSep "\n" raw) ++ "\n\n"
+ contents <- parseFromString parseBlocks $ (intercalate "\n" raw) ++ "\n\n"
return $ BlockQuote contents
--
@@ -757,7 +757,7 @@ multilineTableHeader = try $ do
let rawHeadsList = transpose $ map
(\ln -> tail $ splitByIndices (init indices) ln)
rawContent
- let rawHeads = map (joinWithSep " ") rawHeadsList
+ let rawHeads = map (intercalate " ") rawHeadsList
let aligns = zipWith alignType rawHeadsList lengths
return ((map removeLeadingTrailingSpace rawHeads), aligns, indices)
@@ -884,7 +884,7 @@ mathInline = try $ do
words' <- sepBy1 mathWord (many1 (spaceChar <|> (newline >>~ notFollowedBy' blankline)))
char '$'
notFollowedBy digit
- return $ joinWithSep " " words'
+ return $ intercalate " " words'
emph :: GenParser Char ParserState Inline
emph = ((enclosed (char '*') (notFollowedBy' strong >> char '*') inline) <|>
diff --git a/Text/Pandoc/Readers/RST.hs b/Text/Pandoc/Readers/RST.hs
index 08e55f97d..5533d309f 100644
--- a/Text/Pandoc/Readers/RST.hs
+++ b/Text/Pandoc/Readers/RST.hs
@@ -33,7 +33,7 @@ module Text.Pandoc.Readers.RST (
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.ParserCombinators.Parsec
-import Data.List ( findIndex, delete )
+import Data.List ( findIndex, delete, intercalate )
-- | Parse reStructuredText string and return Pandoc document.
readRST :: ParserState -> String -> Pandoc
@@ -144,7 +144,7 @@ fieldListItem indent = try $ do
first <- manyTill anyChar newline
rest <- option "" $ try $ lookAhead (string indent >> oneOf " \t") >>
indentedBlock
- return (name, joinWithSep " " (first:(lines rest)))
+ return (name, intercalate " " (first:(lines rest)))
fieldList :: GenParser Char ParserState Block
fieldList = try $ do
@@ -583,7 +583,7 @@ code :: GenParser Char ParserState Inline
code = try $ do
string "``"
result <- manyTill anyChar (try (string "``"))
- return $ Code $ removeLeadingTrailingSpace $ joinWithSep " " $ lines result
+ return $ Code $ removeLeadingTrailingSpace $ intercalate " " $ lines result
emph :: GenParser Char ParserState Inline
emph = enclosed (char '*') (char '*') inline >>=