default instance for IsString

Joachim Breitner mail at joachim-breitner.de
Thu Apr 26 00:32:06 CEST 2012


Hi,

Am Mittwoch, den 25.04.2012, 21:57 +0100 schrieb Joachim Breitner:
> Am Mittwoch, den 25.04.2012, 11:15 +0300 schrieb Yitzchak Gale:
> > The only reason I don't like using OverloadedStrings
> > for typing string literals as Text and ByteString
> > is that when you turn on OverloadedStrings, you turn
> > it on for all types, not just Text and ByteString.
> > I don't want to be forced to do that. Because
> > all other uses of OverloadedStrings that I have
> > seen, and there are many, are ill-advised in my
> > opinion. They all should have been quasiquoters.
> 
> another option, quick idea from a pub: Make OverloadedStrings work with
> re-bindable syntax (←needs GHC change, probably) and redefine fromString
> as you want. E.g, if you want to use alwas Text, just define
> 
> fromText :: String -> Text
> 
> in your module (and do not import the IsString method).

actually, this already works somewhat. Take this module:

        {-# LANGUAGE OverloadedStrings, RebindableSyntax #-}
        
        import Prelude
        
        data MyStringType = AnyString deriving Eq
        
        fromString :: String -> MyStringType
        fromString _ = AnyString
        
        test = "test"
        
and see how GHC uses the fromString that I defined; it affects both the
type of test and its value:

Prelude> :r
[1 of 1] Compiling Main             ( /tmp/Test.hs, interpreted )
Ok, modules loaded: Main.
*Main> :t test
test :: MyStringType
*Main> test == AnyString
True


So what is needed for the OP to be happy seems to be either a way to
enable RebindableSytanx _only_ for fromString, or to have a variant of
OverloadedStrings that takes fromString from the module scope. Then he
could define a monomorphic fromString (as I have done) or define its own
typeclass that defines fromString only for desirable types.

With this class definition, declaring IsString instances as save becomes
a one-liner:

        {-# LANGUAGE OverloadedStrings, RebindableSyntax, FlexibleInstances #-}
        
        import Prelude
        import qualified GHC.Exts 
        import Data.Text
        
        class GHC.Exts.IsString a => SafeIsString a where
            fromString :: String -> a
            fromString = GHC.Exts.fromString
        
        instance SafeIsString String 
        instance SafeIsString Text 
        
        test1 :: String
        test1 = "test1"
        
        test2 :: Text
        test2 = "test2"


Prelude> :r
[1 of 1] Compiling Main             ( /tmp/Test.hs, interpreted )
Ok, modules loaded: Main.
*Main> :t (test1,test2)
(test1,test2) :: (String, Text)
*Main> (test1,test2)
Loading package array-0.4.0.0 ... linking ... done.
Loading package bytestring-0.9.2.1 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package text-0.11.1.13 ... linking ... done.
("test1","test2")
*Main> 

Note that if I’d also add

        import Data.ByteString.Char8
        test3 :: ByteString
        test3 = "test3"

I’d get
*Main> :r
[1 of 1] Compiling Main             ( /tmp/Test.hs, interpreted )

/tmp/Test.hs:22:9:
    No instance for (SafeIsString ByteString)
      arising from the literal `"test3"'
    Possible fix:
      add an instance declaration for (SafeIsString ByteString)
    In the expression: "test3"
    In an equation for `test3': test3 = "test3"
Failed, modules loaded: none.

so I am guaranteed not to accidentally call a fromString from an
instance that I have not allowed.

Greetings,
Joachim

PS: Personally, I don’t really think there is a big problem, but
anyways, here is a solution :-)



-- 
Joachim "nomeata" Breitner
  mail at joachim-breitner.de  |  nomeata at debian.org  |  GPG: 0x4743206C
  xmpp: nomeata at joachim-breitner.de | http://www.joachim-breitner.de/

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20120425/879bea1c/attachment.pgp>


More information about the Glasgow-haskell-users mailing list