default instance for IsString

Greg Weber greg at gregweber.info
Mon Apr 23 05:31:25 CEST 2012


Sorry, someone responded on haskell-cafe and the message didn't get
sent here. You can default a String. So this compiles just fine:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
import Data.Text as T
default (T.Text)

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

main = print (noDefault "Hello!")

On Sun, Apr 22, 2012 at 1:57 PM, Jeremy Shaw <jeremy at n-heptane.com> wrote:
> I have often wished for something like:
>
> {-# LANGUAGE StringLiteralsAs Text #-}
>
> where all string literals like:
>
>> f = "foo"
>
> would be translated to:
>
>> f = (fromString "foo" :: Text)
>
> I find that OverloadedStrings is too general and causes ambiguous type
> errors. Additionally, I seldom find that I have more than one type of
> string literal per file. Things tend to be all String, all Text, etc.
> So, if I could just pick a concrete type for all the string literals
> in my file, I would be happy.
>
> - jeremy
>
>
>
> On Sat, Apr 21, 2012 at 7: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