diff options
author | Mark Wright <gienah@gentoo.org> | 2015-01-05 14:40:30 +1100 |
---|---|---|
committer | Mark Wright <gienah@gentoo.org> | 2015-01-05 14:40:30 +1100 |
commit | b748833889dcf21cbe2f418838abb423b565079d (patch) | |
tree | 0ddc928c7143e77a8608c6c80a27599f7e20cda8 /src | |
parent | 10d53989d8ca220315d2d4fc42977d867560f7fd (diff) | |
download | pandoc-b748833889dcf21cbe2f418838abb423b565079d.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')
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 3 |
1 files changed, 2 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 8bfc6f606..b9a77c5d6 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE FlexibleContexts #-} {- Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu> @@ -708,7 +709,7 @@ extractCaption = do toChunks :: String -> [String] toChunks = dropWhile null . map (trim . unlines) - . splitBy (all (`elem` " \t")) . lines + . splitBy (all (`elem` (" \t" :: String))) . lines codeblock :: Maybe String -> String -> String -> RSTParser Blocks codeblock numberLines lang body = |