Hi Simon and all, thanks for the quick response. I somehow suspected it was connected to that...
The mildly surprising effect of adding/leaving out the OverloadedString pragma however made me scratch my head a little, since the following code (w/o pragma) does typecheck just fine (without annotating :: String): import Data.Char (isAlphaNum) main = print $ check str where check = all (\x -> x `elem` valid || isAlphaNum x) valid = "$_-" -- :: String str = "foo_bar123" -- :: String I guess without that pragma, the string literals already imply t ~ [] for Foldable t. Thanks again for the answer, the behaviour I described is to be expected then. Michael 2015-07-30 23:24 GMT+02:00 Simon Peyton Jones <simo...@microsoft.com>: > I think it’s because of the newly generalised Foldable stuff. In 7.10, > after huge discussion (https://ghc.haskell.org/trac/ghc/wiki/Prelude710) > we have > > elem :: (Eq a, Foldable t) => a -> t a -> Bool > > all :: Foldable t => (a -> Bool) -> t a -> Bool > > > > And there is no way to tell what ‘t’ you mean. Lists? Trees? Who knows! > > > > Simon > > > > *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Michael > Karg > *Sent:* 30 July 2015 22:05 > *To:* ghc-devs > *Subject:* Typechecker / OverloadedStrings question 7.8 vs. 7.10 > > > > Hi devs, > > in the followin snippet: > > {-# LANGUAGE OverloadedStrings #-} > import Data.Char (isAlphaNum) > import Data.ByteString.Char8 as BS (all) > main = > print $ check str > where > check = BS.all (\x -> x `elem` valid || isAlphaNum x) -- Line 7 > valid = "$_-" -- :: String > -- Line 8 > str = "foo_bar123" > > GHC 7.10 fails with the following errors (whereas 7.8 compiles without > complaining): > > > ghc --make "Testcase.hs" > [1 of 1] Compiling Main ( Testcase.hs, Testcase.o ) > Testcase.hs:7:31: > No instance for (Foldable t0) arising from a use of ‘elem’ > The type variable ‘t0’ is ambiguous > (...) > > Testcase.hs:8:15: > No instance for (Data.String.IsString (t0 Char)) > arising from the literal ‘"$_-"’ > The type variable ‘t0’ is ambiguous > (...) > > Uncommenting the -- :: String type annotation (line 8) makes the snippet > acceptable to the typechecker however. > > > > So Foldable [] and [Char] should be possible to infer, given the evidence > of 'isAlphaNum x', as obviously happens with GHC 7.8. My question is, how > or why does the 7.10 typechecker behave differently? Is this intentional, > or does this qualify for a trac ticket? > > Thanks for looking into this, > > Michael > > > > PS: The ByteString part is just there since the snippet is taken out of > one of my projects. The following (modified) code only typechecks on 7.10 > with both type annotations uncommented: > > {-# LANGUAGE OverloadedStrings #-} > import Data.Char (isAlphaNum) > main = > print $ check str > where > check = all (\x -> x `elem` valid || isAlphaNum x) > valid = "$_-" -- :: String > str = "foo_bar123" -- :: String > > > > The errors here are (1) no instances for Foldable and (2) no instances for > IsString. > > >
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs