default instance for IsString

Greg Weber greg at gregweber.info
Sun Apr 22 06:55:32 CEST 2012


This is a better demonstration of the issue. I am going to open a GHC
bug report, as I can't see how this behavior is desirable.


{-# LANGUAGE OverloadedStrings #-}
import Data.Text as T

class    NoDefault a      where noDefault :: a -> Text
instance NoDefault T.Text where noDefault = id

main = print (noDefault "Hello!")

default.hs:7:15:
    Ambiguous type variable `a0' in the constraints:
      (NoDefault a0) arising from a use of `noDefault'
                     at default.hs:7:15-23
      (Data.String.IsString a0) arising from the literal `"Hello!"'
                                at default.hs:7:25-32
    Probable fix: add a type signature that fixes these type variable(s)
    In the first argument of `print', namely `(noDefault "Hello!")'
    In the expression: print (noDefault "Hello!")
    In an equation for `main': main = print (noDefault "Hello!")


On Sat, Apr 21, 2012 at 7:51 PM, Greg Weber <greg at gregweber.info> wrote:
> my actual use case looks more like this:
>
> {-# LANGUAGE OverloadedStrings #-}
> {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
>
> import Data.Text as T
>
> class ShowT a where
>   showT :: a -> String
>
> instance ShowT T.Text where
>   showT = show
>
> instance ShowT String where
>   showT = show
>
> main = print (showT "Hello!")
>
>    Ambiguous type variable `a0' in the constraints:
>      (ShowT a0) arising from a use of `showT' at default.hs:16:15-19
>      (Data.String.IsString a0) arising from the literal `"Hello!"'
>
>
> So I actually want to define a default instance for a typeclass I
> define that uses isString instances.
>
>
>
> On Sat, Apr 21, 2012 at 6:24 PM, Daniel Peebles <pumpkingod at gmail.com> wrote:
>> I think it'll be hard to do that without putting Text in base, which I'm not
>> sure anyone wants to do.
>>
>> Dan
>>
>> On Sat, Apr 21, 2012 at 8:20 PM, Greg Weber <greg at gregweber.info> wrote:
>>>
>>> I would like to default IsString to use the Text instance to avoid
>>> ambiguous type errors.
>>> I see defaulting capability is available for Num. Is there any way to
>>> do this for IsString?
>>>
>>> Thanks,
>>> Greg Weber
>>>
>>> _______________________________________________
>>> Glasgow-haskell-users mailing list
>>> Glasgow-haskell-users at haskell.org
>>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>>



More information about the Glasgow-haskell-users mailing list