diff options
author | Mark Wright <gienah@gentoo.org> | 2015-01-05 14:40:06 +1100 |
---|---|---|
committer | Mark Wright <gienah@gentoo.org> | 2015-01-05 14:40:06 +1100 |
commit | 10d53989d8ca220315d2d4fc42977d867560f7fd (patch) | |
tree | 7de1137fc4d437f6128b4a2745ac495256e0df68 /src/Text/Pandoc/Readers | |
parent | f18ceb1b5e9294699699f468ab9fe590b7100704 (diff) | |
download | pandoc-10d53989d8ca220315d2d4fc42977d867560f7fd.tar.gz |
ghc 7.10.1 RC1 requires FlexibleContexts https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#Inferredtype-signaturesnowmayrequiretoenableFlexibleContextsGADTsorTypeFamilies ; ghc 7.10.1 RC1 requires specifying the type of String literals https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysNoinstanceforFoldable...arisingfromtheuseof...
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 7 |
1 files changed, 4 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 440b6d144..f16aed48d 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1,5 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE FlexibleContexts #-} {- Copyright (C) 2014 Albert Krewinkel <tarleb@moltkeplatz.de> @@ -1168,7 +1169,7 @@ isRelativeFilePath s = (("./" `isPrefixOf` s) || ("../" `isPrefixOf` s)) && isUri :: String -> Bool isUri s = let (scheme, path) = break (== ':') s - in all (\c -> isAlphaNum c || c `elem` ".-") scheme + in all (\c -> isAlphaNum c || c `elem` (".-" :: String)) scheme && not (null path) isAbsoluteFilePath :: String -> Bool @@ -1214,7 +1215,7 @@ solidify :: String -> String solidify = map replaceSpecialChar where replaceSpecialChar c | isAlphaNum c = c - | c `elem` "_.-:" = c + | c `elem` ("_.-:" :: String) = c | otherwise = '-' -- | Parses an inline code block and marks it as an babel block. @@ -1465,7 +1466,7 @@ inlineLaTeX = try $ do parseAsMathMLSym :: String -> Maybe Inlines parseAsMathMLSym cs = B.str <$> MathMLEntityMap.getUnicode (clean cs) -- dropWhileEnd would be nice here, but it's not available before base 4.5 - where clean = reverse . dropWhile (`elem` "{}") . reverse . drop 1 + where clean = reverse . dropWhile (`elem` ("{}" :: String)) . reverse . drop 1 state :: ParserState state = def{ stateOptions = def{ readerParseRaw = True }} |