#5858: type inference of an OverloadedString for a class instance with type
parameters
------------------------------+---------------------------------------------
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: |
------------------------------+---------------------------------------------
We have some code in Yesod:
{{{
class RedirectUrl master a where
-- | Converts the value to the URL and a list of query-string
parameters.
toTextUrl :: a -> GHandler sub master Text
instance t ~ Text => RedirectUrl master (Route master, [(t, t)]) where
toTextUrl (u, ps) = do
r <- getUrlRenderParams
return $ r u ps
}}}
When I use it in my application, I am required to give an annotation to
the overloaded strings. If I don't:
{{{
redirect $ (SearchR, [("foo", "bar")])
}}}
I end up with this error message:
{{{
No instance for (RedirectUrl Search (Route Search, [(t0, t1)]))
arising from a use of `redirect'
Possible fix:
add an instance declaration for
(RedirectUrl Search (Route Search, [(t0, t1)]))
In the expression: redirect
In the expression: redirect $ (SearchR, [("foo", "bar")])
In an equation for `getFoodsr23R':
getFoodsr23R foodId = redirect $ (SearchR, [("foo", "bar")])
}}}
I would be ok with having to type annotate if instead of the compiler
suggesting I declare an entire new instance the compiler instead suggested
that I annotate my overloaded strings.
However, in trying to reproduce this program in a simpler setting, it
seems to normally perform the OverloadedStrings inference without any
issue. This works just fine:
{{{
{-# LANGUAGE OverloadedStrings, NoMonomorphismRestriction,
FlexibleInstances, GADTs #-}
module InferOverloaded where
import Data.Text
class InferOverloaded a where
infer :: a -> a
data Data = Data String
instance t ~ Text => InferOverloaded (Data, [(t,t)]) where
infer = id
foo = infer (Data "data", [("overloaded", "strings")])
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5858>
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