default instance for IsString

Albert Y. C. Lai trebla at vex.net
Wed Apr 25 06:38:50 CEST 2012


On 12-04-24 10:11 PM, wren ng thornton wrote:
> To the extent that ByteString's instance runs into issues with high
> point codes, that strikes me as a bug in virtue of poor foresight.
> Consider, for instance, the distinction between integral and
> non-integral numeric literals. We recognize that (0.1 :: Int) is
> invalid, and so we a-priori define the Haskell syntax to recognize two
> different sorts of "numbers". It seems that we should do the same thing
> for strings. 'String' literals of raw binary goop (subject to escape
> mechanisms for detecting the end of string) are different from string
> literals which are valid Unicode sequences. This, I think, is fair game
> to be expressed directly in the specification of overloaded string
> literals, just as we distinguish classes of overloaded numeric literals.
> Unfortunately, for numeric literals we have a nice syntactic distinction
> between integral and non-integral, which seems to suggest that we'd need
> a similar syntactic distinction to recognize the different sorts of
> string literals.

I have a cunning plan:

class IsList c e | c -> e where
   fromList :: [e] -> c
   -- requirement: must be a total function

instance IsList ByteString Word8 where
   fromList = ByteString.pack

instance Ord e => IsList (Set e) e where
   fromList = Set.fromList

{-# LANGUAGE OverloadedList #-}

example1 :: ByteString
example1 = [106,117,115,116,32,107,105,100,100,105,110,103]

example2 :: Set Word8
example2 = [106,117,115,116,32,107,105,100,100,105,110,103]

Please don't kill me!



More information about the Glasgow-haskell-users mailing list