aboutsummaryrefslogtreecommitdiff
path: root/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-09-08 06:36:28 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-09-08 06:36:28 +0000
commit000b89c718fdef3790a56fad9cbbfcdcf7fbea52 (patch)
tree9603419213adad41e8b246a4ae660cf206d04e42 /Text/Pandoc/Writers
parent2e893b43c4b0536957d46289e7f64b4943734bda (diff)
downloadpandoc-000b89c718fdef3790a56fad9cbbfcdcf7fbea52.tar.gz
Use Data.List's 'intercalate' instead of custom 'joinWithSep'.
+ Removed joinWithSep definition from Text.Pandoc.Shared. + Replaced joinWithSep with intercalate + Depend on base >= 3, since in base < 3 intercalate is not included. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1428 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'Text/Pandoc/Writers')
-rw-r--r--Text/Pandoc/Writers/ConTeXt.hs6
-rw-r--r--Text/Pandoc/Writers/Docbook.hs4
-rw-r--r--Text/Pandoc/Writers/HTML.hs4
-rw-r--r--Text/Pandoc/Writers/LaTeX.hs4
-rw-r--r--Text/Pandoc/Writers/Man.hs8
-rw-r--r--Text/Pandoc/Writers/Markdown.hs4
-rw-r--r--Text/Pandoc/Writers/OpenDocument.hs3
-rw-r--r--Text/Pandoc/Writers/RTF.hs6
-rw-r--r--Text/Pandoc/Writers/S5.hs5
9 files changed, 23 insertions, 21 deletions
diff --git a/Text/Pandoc/Writers/ConTeXt.hs b/Text/Pandoc/Writers/ConTeXt.hs
index 3af997374..014751968 100644
--- a/Text/Pandoc/Writers/ConTeXt.hs
+++ b/Text/Pandoc/Writers/ConTeXt.hs
@@ -31,7 +31,7 @@ module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Printf ( printf )
-import Data.List ( isSuffixOf )
+import Data.List ( isSuffixOf, intercalate )
import Control.Monad.State
import Text.PrettyPrint.HughesPJ hiding ( Str )
@@ -87,7 +87,7 @@ contextHeader options (Meta title authors date) = do
then ""
else if length authors == 1
then stringToConTeXt $ head authors
- else stringToConTeXt $ (joinWithSep ", " $
+ else stringToConTeXt $ (intercalate ", " $
init authors) ++ " & " ++ last authors
let datetext = if date == ""
then ""
@@ -168,7 +168,7 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do
let specs2Items = filter (not . null) [start', delim', width'']
let specs2 = if null specs2Items
then ""
- else "[" ++ joinWithSep "," specs2Items ++ "]"
+ else "[" ++ intercalate "," specs2Items ++ "]"
let style'' = case style' of
DefaultStyle -> orderedListStyles !! level
Decimal -> "[n]"
diff --git a/Text/Pandoc/Writers/Docbook.hs b/Text/Pandoc/Writers/Docbook.hs
index 025727076..3e535a87e 100644
--- a/Text/Pandoc/Writers/Docbook.hs
+++ b/Text/Pandoc/Writers/Docbook.hs
@@ -32,7 +32,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.XML
import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
-import Data.List ( isPrefixOf, drop )
+import Data.List ( isPrefixOf, drop, intercalate )
import Text.PrettyPrint.HughesPJ hiding ( Str )
-- | Convert list of authors to a docbook <author> section
@@ -50,7 +50,7 @@ authorToDocbook name = inTagsIndented "author" $
(firstname, lastname) = case lengthname of
0 -> ("","")
1 -> ("", name)
- n -> (joinWithSep " " (take (n-1) namewords), last namewords)
+ n -> (intercalate " " (take (n-1) namewords), last namewords)
in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
inTagsSimple "surname" (text $ escapeStringForXML lastname)
diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs
index 066a39090..b1e6dabc1 100644
--- a/Text/Pandoc/Writers/HTML.hs
+++ b/Text/Pandoc/Writers/HTML.hs
@@ -37,7 +37,7 @@ import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Highlighting ( highlightHtml, defaultHighlightingCss )
import Numeric ( showHex )
import Data.Char ( ord, toLower, isAlpha )
-import Data.List ( isPrefixOf, intersperse )
+import Data.List ( isPrefixOf, intercalate )
import qualified Data.Set as S
import Control.Monad.State
import Text.XHtml.Transitional hiding ( stringToHtml )
@@ -252,7 +252,7 @@ inlineListToIdentifier' (x:xs) =
xAsText ++ inlineListToIdentifier' xs
where xAsText = case x of
Str s -> filter (\c -> c == '-' || not (isPunctuation c)) $
- concat $ intersperse "-" $ words $ map toLower s
+ intercalate "-" $ words $ map toLower s
Emph lst -> inlineListToIdentifier' lst
Strikeout lst -> inlineListToIdentifier' lst
Superscript lst -> inlineListToIdentifier' lst
diff --git a/Text/Pandoc/Writers/LaTeX.hs b/Text/Pandoc/Writers/LaTeX.hs
index a13c51b30..8b8f87c57 100644
--- a/Text/Pandoc/Writers/LaTeX.hs
+++ b/Text/Pandoc/Writers/LaTeX.hs
@@ -31,7 +31,7 @@ module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Printf ( printf )
-import Data.List ( (\\), isSuffixOf )
+import Data.List ( (\\), isSuffixOf, intercalate )
import Data.Char ( toLower )
import qualified Data.Set as S
import Control.Monad.State
@@ -92,7 +92,7 @@ latexHeader options (Meta title authors date) = do
then text "\\VerbatimFootnotes % allows verbatim text in footnotes"
else empty
let authorstext = text $ "\\author{" ++
- joinWithSep "\\\\" (map stringToLaTeX authors) ++ "}"
+ intercalate "\\\\" (map stringToLaTeX authors) ++ "}"
let datetext = if date == ""
then empty
else text $ "\\date{" ++ stringToLaTeX date ++ "}"
diff --git a/Text/Pandoc/Writers/Man.hs b/Text/Pandoc/Writers/Man.hs
index 0bd6b92ef..210c7ed07 100644
--- a/Text/Pandoc/Writers/Man.hs
+++ b/Text/Pandoc/Writers/Man.hs
@@ -32,7 +32,7 @@ module Text.Pandoc.Writers.Man ( writeMan) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Printf ( printf )
-import Data.List ( isPrefixOf, drop, nub, intersperse )
+import Data.List ( isPrefixOf, drop, nub, intersperse, intercalate )
import Text.PrettyPrint.HughesPJ hiding ( Str )
import Control.Monad.State
@@ -77,8 +77,8 @@ metaToMan options (Meta title authors date) = do
doubleQuotes (text date) <+> hsep extras
let foot = case length authors of
0 -> empty
- 1 -> text ".SH AUTHOR" $$ (text $ joinWithSep ", " authors)
- _ -> text ".SH AUTHORS" $$ (text $ joinWithSep ", " authors)
+ 1 -> text ".SH AUTHOR" $$ (text $ intercalate ", " authors)
+ _ -> text ".SH AUTHORS" $$ (text $ intercalate ", " authors)
return $ if writerStandalone options
then (head', foot)
else (empty, empty)
@@ -144,7 +144,7 @@ blockToMan opts (Table caption alignments widths headers rows) =
modify (\(notes, preprocessors) -> (notes, "t":preprocessors))
let iwidths = map (printf "w(%0.2fn)" . (70 *)) widths
-- 78n default width - 8n indent = 70n
- let coldescriptions = text $ joinWithSep " "
+ let coldescriptions = text $ intercalate " "
(zipWith (\align width -> aligncode align ++ width)
alignments iwidths) ++ "."
colheadings <- mapM (blockListToMan opts) headers
diff --git a/Text/Pandoc/Writers/Markdown.hs b/Text/Pandoc/Writers/Markdown.hs
index d8ad8454f..32ebcf758 100644
--- a/Text/Pandoc/Writers/Markdown.hs
+++ b/Text/Pandoc/Writers/Markdown.hs
@@ -34,7 +34,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Blocks
import Text.ParserCombinators.Parsec ( parse, GenParser )
-import Data.List ( group, isPrefixOf, drop, find, intersperse )
+import Data.List ( group, isPrefixOf, drop, find, intersperse, intercalate )
import Text.PrettyPrint.HughesPJ hiding ( Str )
import Control.Monad.State
@@ -119,7 +119,7 @@ titleToMarkdown opts lst = do
authorsToMarkdown :: [String] -> State WriterState Doc
authorsToMarkdown [] = return empty
authorsToMarkdown lst = return $
- text "% " <> text (joinWithSep ", " (map escapeString lst))
+ text "% " <> text (intercalate ", " (map escapeString lst))
dateToMarkdown :: String -> State WriterState Doc
dateToMarkdown [] = return empty
diff --git a/Text/Pandoc/Writers/OpenDocument.hs b/Text/Pandoc/Writers/OpenDocument.hs
index 5ba92368e..a49bed49f 100644
--- a/Text/Pandoc/Writers/OpenDocument.hs
+++ b/Text/Pandoc/Writers/OpenDocument.hs
@@ -39,6 +39,7 @@ import Control.Applicative ( (<$>) )
import Control.Arrow ( (***), (>>>) )
import Control.Monad.State hiding ( when )
import Data.Char (chr)
+import Data.List (intercalate)
-- | Auxiliary function to convert Plain block to Para.
plainToPara :: Block -> Block
@@ -171,7 +172,7 @@ authorToOpenDocument name =
(firstname, lastname) = case lengthname of
0 -> ("","")
1 -> ("", name)
- n -> (joinWithSep " " (take (n-1) namewords), last namewords)
+ n -> (intercalate " " (take (n-1) namewords), last namewords)
in inParagraphTagsWithStyle "Author" $
(text $ escapeStringForXML firstname) <+>
(text $ escapeStringForXML lastname)
diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs
index 002ef7edc..fc6cd1bf0 100644
--- a/Text/Pandoc/Writers/RTF.hs
+++ b/Text/Pandoc/Writers/RTF.hs
@@ -31,7 +31,7 @@ module Text.Pandoc.Writers.RTF ( writeRTF ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
-import Data.List ( isSuffixOf )
+import Data.List ( isSuffixOf, intercalate )
import Data.Char ( ord, isDigit )
-- | Convert Pandoc to a string in rich text format.
@@ -82,7 +82,7 @@ stringToRTF = handleUnicode . escapeSpecial
-- | Escape things as needed for code block in RTF.
codeStringToRTF :: String -> String
-codeStringToRTF str = joinWithSep "\\line\n" $ lines (stringToRTF str)
+codeStringToRTF str = intercalate "\\line\n" $ lines (stringToRTF str)
-- | Make a paragraph with first-line indent, block indent, and space after.
rtfParSpaced :: Int -- ^ space after (in twips)
@@ -150,7 +150,7 @@ rtfHeader headerText (Meta title authors date) =
"\\b \\fs36 " ++ inlineListToRTF title
authorstext = if null authors
then ""
- else rtfPar 0 0 AlignCenter (" " ++ (joinWithSep "\\" $
+ else rtfPar 0 0 AlignCenter (" " ++ (intercalate "\\" $
map stringToRTF authors))
datetext = if date == ""
then ""
diff --git a/Text/Pandoc/Writers/S5.hs b/Text/Pandoc/Writers/S5.hs
index 59e1a40ab..6f528503a 100644
--- a/Text/Pandoc/Writers/S5.hs
+++ b/Text/Pandoc/Writers/S5.hs
@@ -40,12 +40,13 @@ module Text.Pandoc.Writers.S5 (
writeS5String,
insertS5Structure
) where
-import Text.Pandoc.Shared ( joinWithSep, WriterOptions )
+import Text.Pandoc.Shared ( WriterOptions )
import Text.Pandoc.TH ( contentsOf )
import Text.Pandoc.Writers.HTML ( writeHtml, writeHtmlString )
import Text.Pandoc.Definition
import Text.XHtml.Strict
import System.FilePath ( (</>) )
+import Data.List ( intercalate )
s5Meta :: String
s5Meta = "<!-- configuration parameters -->\n<meta name=\"defaultView\" content=\"slideshow\" />\n<meta name=\"controlVis\" content=\"hidden\" />\n"
@@ -148,7 +149,7 @@ insertS5Structure (Pandoc (Meta title' authors date) blocks) =
let slides = insertSlides True blocks
firstSlide = if not (null title')
then [slideStart, (Header 1 title'),
- (Header 3 [Str (joinWithSep ", " authors)]),
+ (Header 3 [Str (intercalate ", " authors)]),
(Header 4 [Str date]), slideEnd]
else []
newBlocks = (layoutDiv title' date) ++ presentationStart:firstSlide ++