default instance for IsString

Michael Snoyman michael at snoyman.com
Tue Apr 24 11:41:24 CEST 2012


On Tue, Apr 24, 2012 at 12:35 PM, Yitzchak Gale <gale at sefer.org> wrote:
> Markus Läll wrote:
>> You do know, that you already *can* have safe Text and ByteString from
>> an overloaded string literal.
>
> Yes, the IsString instances for Text and ByteString are safe
> (I hope).
>
> But in order to use them, I have to turn on OverloadedStrings.
> That could cause other string literals in the same module
> to throw exceptions at run time.
>
> -Yitz
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Actually, the ByteString instance is arguably unsafe as well:

{-# LANGUAGE OverloadedStrings #-}
import qualified Data.ByteString.Char8 as S8

main = S8.putStrLn "שלום"

It would be nice if usage of characters outside of the 0-255 range
could be caught at compile time.

Michael



More information about the Glasgow-haskell-users mailing list