#6030: Typeclass constraint should pick the OverloadedString type.
------------------------------+---------------------------------------------
Reporter: GregWeber | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.4.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
------------------------------+---------------------------------------------
Comment(by michalt):
I don't really see a problem/bug here. The type is ambiguous and according
to
[http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-
extensions.html#overloaded-strings documentation]
the defaulting mechanism (IIRC to ```String```) will not work here:
The standard defaulting rule (Haskell Report, Section 4.3.4) is extended
thus:
defaulting applies when all the unresolved constraints involve standard
classes
or IsString; and at least one is a numeric class or IsString.
So it's like writing:
{{{
module Main where
class Foo a where
foo :: a -> ()
main = print (foo $ 0)
}}}
which results in
{{{
[1 of 1] Compiling Main ( Test.hs, interpreted )
Test.hs:6:21:
Ambiguous type variable `a0' in the constraints:
(Num a0) arising from the literal `0' at Test.hs:6:21
(Foo a0) arising from a use of `foo' at Test.hs:6:15-17
Probable fix: add a type signature that fixes these type variable(s)
In the second argument of `($)', namely `0'
In the first argument of `print', namely `(foo $ 0)'
In the expression: print (foo $ 0)
Failed, modules loaded: none.
}}}
Am I missing something?
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6030#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs