aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs2
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs2
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs2
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs12
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--src/Text/Pandoc/Writers/RST.hs6
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs2
8 files changed, 15 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index ebdc4a3d3..edfb4d0ff 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -119,7 +119,7 @@ stringToConTeXt opts = concatMap (escapeCharForConTeXt opts)
toLabel :: String -> String
toLabel z = concatMap go z
where go x
- | elem x "\\#[]\",{}%()|=" = "ux" ++ printf "%x" (ord x)
+ | elem x ("\\#[]\",{}%()|=" :: String) = "ux" ++ printf "%x" (ord x)
| otherwise = [x]
-- | Convert Elements to ConTeXt
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 32da3a2d3..212206ac6 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards, CPP, ScopedTypeVariables, ViewPatterns #-}
+{-# LANGUAGE PatternGuards, CPP, ScopedTypeVariables, ViewPatterns, FlexibleContexts #-}
{-
Copyright (C) 2010-2014 John MacFarlane <jgm@berkeley.edu>
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 181c63df7..75afa43e5 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
{- |
Module : Text.Pandoc.Writers.ICML
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 3698d275c..eb514698a 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -240,7 +240,7 @@ toLabel z = go `fmap` stringToLaTeX URLString z
where go [] = ""
go (x:xs)
| (isLetter x || isDigit x) && isAscii x = x:go xs
- | elem x "-+=:;." = x:go xs
+ | elem x ("-+=:;." :: String) = x:go xs
| otherwise = "ux" ++ printf "%x" (ord x) ++ go xs
-- | Puts contents into LaTeX command.
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index f06f1d6cc..d71f0daf8 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -323,9 +323,9 @@ blockToMarkdown opts (Plain inlines) = do
then Just $ writerColumns opts
else Nothing
let rendered = render colwidth contents
- let escapeDelimiter (x:xs) | x `elem` ".()" = '\\':x:xs
- | otherwise = x : escapeDelimiter xs
- escapeDelimiter [] = []
+ let escapeDelimiter (x:xs) | x `elem` (".()" :: String) = '\\':x:xs
+ | otherwise = x : escapeDelimiter xs
+ escapeDelimiter [] = []
let contents' = if isEnabled Ext_all_symbols_escapable opts &&
not (stPlain st) && beginsWithOrderedListMarker rendered
then text $ escapeDelimiter rendered
@@ -681,7 +681,7 @@ inlineListToMarkdown opts lst =
mapM (inlineToMarkdown opts) (avoidBadWraps lst) >>= return . cat
where avoidBadWraps [] = []
avoidBadWraps (Space:Str (c:cs):xs)
- | c `elem` "-*+>" = Str (' ':c:cs) : avoidBadWraps xs
+ | c `elem` ("-*+>" :: String) = Str (' ':c:cs) : avoidBadWraps xs
avoidBadWraps (x:xs) = x : avoidBadWraps xs
escapeSpaces :: Inline -> Inline
@@ -821,8 +821,8 @@ inlineToMarkdown opts (Cite (c:cs) lst)
sdoc <- inlineListToMarkdown opts sinlines
let k' = text (modekey m ++ "@" ++ k)
r = case sinlines of
- Str (y:_):_ | y `elem` ",;]@" -> k' <> sdoc
- _ -> k' <+> sdoc
+ Str (y:_):_ | y `elem` (",;]@" :: String) -> k' <> sdoc
+ _ -> k' <+> sdoc
return $ pdoc <+> r
modekey SuppressAuthor = "-"
modekey _ = ""
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 773d142f4..901f827fb 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards, OverloadedStrings #-}
+{-# LANGUAGE PatternGuards, OverloadedStrings, FlexibleContexts #-}
{-
Copyright (C) 2008-2014 Andrea Rossato <andrea.rossato@ing.unitn.it>
and John MacFarlane.
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 5ba4c9983..717a47000 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -105,7 +105,7 @@ keyToRST :: ([Inline], (String, String))
-> State WriterState Doc
keyToRST (label, (src, _)) = do
label' <- inlineListToRST label
- let label'' = if ':' `elem` (render Nothing label')
+ let label'' = if ':' `elem` ((render Nothing label') :: String)
then char '`' <> label' <> char '`'
else label'
return $ nowrap $ ".. _" <> label'' <> ": " <> text src
@@ -333,12 +333,12 @@ inlineListToRST lst =
okAfterComplex :: Inline -> Bool
okAfterComplex Space = True
okAfterComplex LineBreak = True
- okAfterComplex (Str (c:_)) = isSpace c || c `elem` "-.,:;!?\\/'\")]}>–—"
+ okAfterComplex (Str (c:_)) = isSpace c || c `elem` ("-.,:;!?\\/'\")]}>–—" :: String)
okAfterComplex _ = False
okBeforeComplex :: Inline -> Bool
okBeforeComplex Space = True
okBeforeComplex LineBreak = True
- okBeforeComplex (Str (c:_)) = isSpace c || c `elem` "-:/'\"<([{–—"
+ okBeforeComplex (Str (c:_)) = isSpace c || c `elem` ("-:/'\"<([{–—" :: String)
okBeforeComplex _ = False
isComplex :: Inline -> Bool
isComplex (Emph _) = True
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 8ac717bab..8fd177fd3 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -368,7 +368,7 @@ inlineListForNode = return . text . stringToTexinfo .
-- periods, commas, colons, and parentheses are disallowed in node names
disallowedInNode :: Char -> Bool
-disallowedInNode c = c `elem` ".,:()"
+disallowedInNode c = c `elem` (".,:()" :: String)
-- | Convert inline element to Texinfo
inlineToTexinfo :: Inline -- ^ Inline to convert