Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Phil Ruffwind
> Would someone feel able to open a Trac ticket summarising this thread (as 
> well as pointing to it), and making a proposal?

Done: https://ghc.haskell.org/trac/ghc/ticket/10733
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Simon Peyton Jones
Would someone feel able to open a Trac ticket summarising this thread (as well 
as pointing to it), and making a proposal?

Thanks

Simon

| -Original Message-
| From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Daniel
| Bergey
| Sent: 03 August 2015 17:47
| To: Phil Ruffwind; Reid Barton
| Cc: ghc-devs
| Subject: Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10
| 
| On 2015-08-03 at 04:43, Phil Ruffwind  wrote:
| > I think the error message could be made clearer simply by emphasizing
| the fact
| > that type ambiguity over the lack of instances.
| >
| > Ambiguous type variable 't0' arising from a use of
| >   elem :: a -> t0 a -> Bool
| > caused by the lack of an instance 'Data.String.IsString (t0 Char)'
| > Either add a type annotation to dictate what 't0' should be
| > based on one of the potential instances:
| >   instance Foldable (Either a) -- Defined in ‘Data.Foldable’
| >   instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’
| >   instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)
| > -- Defined in ‘Data.Foldable’
| >   ...plus three others)
| > or define the required instance 'Data.String.IsString (t0 Char)'.
| 
| Yes, I think that message would be fine.
| ___
| ghc-devs mailing list
| ghc-devs@haskell.org
| http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Phil Ruffwind
Like this?

Either use a type annotation to specify what 't0' should be
based on these potential instance(s):
  instance Foo Bar -- Defined in 'Foo.Bar'
  ... and possibly more from other modules that
  the compiler has not yet encountered
or define the required instance 'Foo t0'

Not sure how best to present this.  To explain this properly it's
going to take several lines :\

---

Some other more general suggestions: it'd be nice to have

- a unique tag for each GHC error, like 'ambiguous-type-variable' to
improve searchability of error messages from GHC.  The tag would also
remain constant while the message may change over time.

- a wiki that documents all the GHC errors.  Not merely beginner-level
advice, but also explanations of what causes them in all its gory
details (so discussions like this could be pasted into that, for
example).  There is a stub already on
https://wiki.haskell.org/GHC/Error_messages but it looks largely
abandoned :(
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Reid Barton
On Mon, Aug 3, 2015 at 12:43 AM, Phil Ruffwind  wrote:

> I think the error message could be made clearer simply by emphasizing the
> fact
> that type ambiguity over the lack of instances.
>
> Ambiguous type variable 't0' arising from a use of
>   elem :: a -> t0 a -> Bool
> caused by the lack of an instance 'Data.String.IsString (t0 Char)'
> Either add a type annotation to dictate what 't0' should be
> based on one of the potential instances:
>   instance Foldable (Either a) -- Defined in ‘Data.Foldable’
>   instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’
>   instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)
> -- Defined in ‘Data.Foldable’
>   ...plus three others)
> or define the required instance 'Data.String.IsString (t0 Char)'.
>

I like this style of error message since it points to the most likely fix
first.

If there are no "potential instances" (instances for specializations of the
type we need an instance for) in scope, then we can produce the old
"No instance for C t0" error, which suggests that the user write (or import)
such an instance. If there is at least one "potential instance" in scope,
then (assuming that the user wants to keep their existing instances,
and not use overlapping instances) they in fact must specify the type
variable somehow.

The only case that may still cause confusion is when there is exactly one
"potential instance" in scope. Then the user is likely to wonder why the
type is ambiguous. It might help to phrase the error message text in a
way that implies that the list of instances it displays is not necessarily
exhaustive.

Regards,
Reid Barton
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Iavor Diatchki
Hello,

what Reid says is exactly right---the issue is not really about what
instances are present, the problem is that GHC can't determine how to
instantiate `t0`.
Perhaps a more direct way to describe this is as follows:

Failed to infer type `t0`
  while solving constraint `Data.String.IsString (t0 Char)`
  arising from the use of:
elem :: a -> t0 a -> Bool

-Iavor





On Mon, Aug 3, 2015 at 9:47 AM, Brandon Allbery  wrote:

> On Mon, Aug 3, 2015 at 12:45 PM, Daniel Bergey 
> wrote:
>
>> I thought GHC would infer the type when only one instance is in scope,
>> at least in some cases, like IsString.  But I could well be wrong about
>> that.
>>
>
> Typeclasses are open-world; this is not a safe assumption, since instances
> are global and an instance added elsewhere at some point in the future
> could therefore break your program.
>
> --
> brandon s allbery kf8nh   sine nomine
> associates
> allber...@gmail.com
> ballb...@sinenomine.net
> unix, openafs, kerberos, infrastructure, xmonad
> http://sinenomine.net
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Brandon Allbery
On Mon, Aug 3, 2015 at 12:45 PM, Daniel Bergey  wrote:

> I thought GHC would infer the type when only one instance is in scope,
> at least in some cases, like IsString.  But I could well be wrong about
> that.
>

Typeclasses are open-world; this is not a safe assumption, since instances
are global and an instance added elsewhere at some point in the future
could therefore break your program.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Daniel Bergey
On 2015-08-03 at 04:43, Phil Ruffwind  wrote:
> I think the error message could be made clearer simply by emphasizing the fact
> that type ambiguity over the lack of instances.
>
> Ambiguous type variable 't0' arising from a use of
>   elem :: a -> t0 a -> Bool
> caused by the lack of an instance 'Data.String.IsString (t0 Char)'
> Either add a type annotation to dictate what 't0' should be
> based on one of the potential instances:
>   instance Foldable (Either a) -- Defined in ‘Data.Foldable’
>   instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’
>   instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)
> -- Defined in ‘Data.Foldable’
>   ...plus three others)
> or define the required instance 'Data.String.IsString (t0 Char)'.

Yes, I think that message would be fine.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-03 Thread Daniel Bergey
On 2015-08-02 at 23:17, Reid Barton  wrote:
> It may be worth noting that the existing error message is actually
> technically
> correct, in the sense that what would be needed for the program to compile
> is exactly an instance of the form "instance Foldable t where ...". Then the
> compiler would know that the ambiguity in the type variable t0 doesn't
> matter.
> It doesn't make any difference whether there are zero, one, or multiple
> instances
> of Foldable for more specific types. (Except in that if there is at least
> one
> such instance, then there can't also be an "instance Foldable t" assuming
> that OverlappingInstances is not enabled.) Once you understand this, the
> error
> message makes perfect sense.

I thought GHC would infer the type when only one instance is in scope,
at least in some cases, like IsString.  But I could well be wrong about that.

> But it is often confusing to beginners.

I think it is beginners who are most affected by the wording of error
messages.  With time, the errors are familiar - I know how I fixed the
last dozen similar errors, and can fix the next one the same way.  But
for beginners, the messages serve as explanations of what is wrong, and
they ought to be worded to make sense to beginners.  

> "Multiple instances for (C t)" seems bad because there might not be any
> instances for C at all.

My initial question was whether GHC can give a different message when
there are multiple instances than when there is none.  I appreciate your
point that these are not so different, but that's an insight that helps
me today, not a Haskell newcomer I was several years ago.  (Though GHC
today lists several matching instances, which is a great improvement
over the behavior in 7.4 when I was learning this.)

> "No unique instance for (C t)" is better most of
> the time,
> but it doesn't exactly get to the core of the issue, since there could be
> just one
> instance of C, for a specific type, and then it is no better than "No
> instance for
> (C t)". If I were to explain the situation, I would say "there is no single
> instance
> (C t) that applies for every type t", but it seems a bit wordy for a
> compiler error...
>
> Regards,
> Reid Barton
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-02 Thread Phil Ruffwind
I think the error message could be made clearer simply by emphasizing the fact
that type ambiguity over the lack of instances.

Ambiguous type variable 't0' arising from a use of
  elem :: a -> t0 a -> Bool
caused by the lack of an instance 'Data.String.IsString (t0 Char)'
Either add a type annotation to dictate what 't0' should be
based on one of the potential instances:
  instance Foldable (Either a) -- Defined in ‘Data.Foldable’
  instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’
  instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)
-- Defined in ‘Data.Foldable’
  ...plus three others)
or define the required instance 'Data.String.IsString (t0 Char)'.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-02 Thread Reid Barton
On Sun, Aug 2, 2015 at 12:58 PM, Daniel Bergey  wrote:

> On 2015-07-31 at 08:59, Simon Peyton Jones  wrote:
> > Daniel Bergey wrote:
> > |  How hard would it be to give a different error message instead of "No
> > |  instance ..." when the type variable is ambiguous?  I always find this
> > |  error slightly misleading, since it seems to me that there are
> > |  multiple valid instances, not that there is "no instance".
> >
> > What would you like it to say?  I think it likely we could make it say
> that!
>
> Great!  I'd like it to say "Multiple instances for ..."  or "No unique
> instance for ...".  I have a slight preference for the former.
>

It may be worth noting that the existing error message is actually
technically
correct, in the sense that what would be needed for the program to compile
is exactly an instance of the form "instance Foldable t where ...". Then the
compiler would know that the ambiguity in the type variable t0 doesn't
matter.
It doesn't make any difference whether there are zero, one, or multiple
instances
of Foldable for more specific types. (Except in that if there is at least
one
such instance, then there can't also be an "instance Foldable t" assuming
that OverlappingInstances is not enabled.) Once you understand this, the
error
message makes perfect sense. But it is often confusing to beginners.

"Multiple instances for (C t)" seems bad because there might not be any
instances for C at all. "No unique instance for (C t)" is better most of
the time,
but it doesn't exactly get to the core of the issue, since there could be
just one
instance of C, for a specific type, and then it is no better than "No
instance for
(C t)". If I were to explain the situation, I would say "there is no single
instance
(C t) that applies for every type t", but it seems a bit wordy for a
compiler error...

Regards,
Reid Barton
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-08-02 Thread Daniel Bergey
On 2015-07-31 at 08:59, Simon Peyton Jones  wrote:
> Daniel Bergey wrote:
> |  How hard would it be to give a different error message instead of "No
> |  instance ..." when the type variable is ambiguous?  I always find this
> |  error slightly misleading, since it seems to me that there are
> |  multiple valid instances, not that there is "no instance".
>
> What would you like it to say?  I think it likely we could make it say that!

Great!  I'd like it to say "Multiple instances for ..."  or "No unique
instance for ...".  I have a slight preference for the former.

Daniel
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-07-31 Thread Simon Peyton Jones
|  How hard would it be to give a different error message instead of "No
|  instance ..." when the type variable is ambiguous?  I always find this
|  error slightly misleading, since it seems to me that there are
|  multiple valid instances, not that there is "no instance".

What would you like it to say?  I think it likely we could make it say that!

S

|  -Original Message-
|  From: Daniel Bergey [mailto:ber...@teallabs.org]
|  Sent: 31 July 2015 02:23
|  To: Michael Karg; Simon Peyton Jones
|  Cc: ghc-devs
|  Subject: Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10
|  
|  On 2015-07-30 at 21:39, Michael Karg  wrote:
|  > I guess without that pragma, the string literals already imply t ~
|  []
|  > for Foldable t.
|  
|  You're basically right.  Without OverloadedStrings, a string literal
|  ("foo") is always a String.  With OverloadedStrings, it's free to be
|  any t such that IsString t.  (But it's expected to have a monomorphic
|  type, not the polymorphic "foo" :: forall t. IsString t => t)
|  
|  Hence the second error below - GHC tries to pick a type that is both
|  Foldable and IsString, but that's not a unique combination.
|  
|  >> 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
|  >> (...)
|  
|  Question for GHC devs:
|  
|  How hard would it be to give a different error message instead of "No
|  instance ..." when the type variable is ambiguous?  I always find this
|  error slightly misleading, since it seems to me that there are
|  multiple valid instances, not that there is "no instance".
|  
|  bergey
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-07-30 Thread Daniel Bergey
On 2015-07-30 at 21:39, Michael Karg  wrote:
> I guess without that pragma, the string literals already imply t ~ [] for
> Foldable t.

You're basically right.  Without OverloadedStrings, a string literal
("foo") is always a String.  With OverloadedStrings, it's free to be
any t such that IsString t.  (But it's expected to have a monomorphic
type, not the polymorphic "foo" :: forall t. IsString t => t)

Hence the second error below - GHC tries to pick a type that is both
Foldable and IsString, but that's not a unique combination.

>> 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
>> (...)

Question for GHC devs:

How hard would it be to give a different error message instead of "No
instance ..." when the type variable is ambiguous?  I always find this
error slightly misleading, since it seems to me that there are multiple
valid instances, not that there is "no instance".

bergey
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-07-30 Thread Michael Karg
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 :

> 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


RE: Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-07-30 Thread Simon Peyton Jones
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


Typechecker / OverloadedStrings question 7.8 vs. 7.10

2015-07-30 Thread Michael Karg
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