default instance for IsString

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

Pretty sure it does default to String, anyway: {-# LANGUAGE OverloadedStrings #-} main = print (show "Hello!")

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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I do not think this is a bug. Since type classes are open, GHC does not do any reasoning of the form "X is the only instance in scope, so I will pick that one". Other instances could be added at any time (perhaps in other modules). In this particular instance, GHC has no reason to choose the Text instance other than the fact that it is the only instance in scope -- that is, type inference is not enough to determine that the Text instance should be chosen. However, I do agree that it would be nice to have a mechanism for specifying default instances for arbitrary (user-defined) type classes. -Brent On Sat, Apr 21, 2012 at 09:55:32PM -0700, Greg Weber wrote:
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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Sun, Apr 22, 2012 at 10:37 AM, Brent Yorgey
I do not think this is a bug. Since type classes are open, GHC does not do any reasoning of the form "X is the only instance in scope, so I will pick that one". Other instances could be added at any time (perhaps in other modules). In this particular instance, GHC has no reason to choose the Text instance other than the fact that it is the only instance in scope -- that is, type inference is not enough to determine that the Text instance should be chosen.
However, I do agree that it would be nice to have a mechanism for specifying default instances for arbitrary (user-defined) type classes.
Couldn't we make a special case for IsString, like we do for Num, given it's special syntactic association with OverloadedStrings? -- Johan

| Couldn't we make a special case for IsString, like we do for Num,
| given it's special syntactic association with OverloadedStrings?
Maybe so. It's open to anyone to make a concrete proposal. See
http://hackage.haskell.org/trac/ghc/ticket/6030
which may be the same issue.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-
| bounces@haskell.org] On Behalf Of Johan Tibell
| Sent: 22 April 2012 18:51
| To: Brent Yorgey
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: default instance for IsString
|
| On Sun, Apr 22, 2012 at 10:37 AM, Brent Yorgey

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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Jeremy Shaw 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)
Agreed, I would also really like this.
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.
In addition, OverloadedStrings is unsound. Library authors can, and do, write unsafe implementations of IsString that cause syntax errors to be caught only at run time instead of at compile time. That is the opposite of one of the most important things we are trying to accomplish by using Haskell instead of, say, some dynamically typed language. Greg Weber wrote:
You can default a String. So this compiles just fine:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} import Data.Text as T default (T.Text)
No, I do not want string literals to be polymorphic, even if there is some kind of defaulting. I want them to be monomorphic, as they always have been. But I still want to be able to specify to the compiler somehow that the monomorphic type for string literals in a particular module should be something other than String. Thanks, Yitz

On Mon, Apr 23, 2012 at 9:58 AM, Yitzchak Gale
Jeremy Shaw 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)
Agreed, I would also really like this.
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.
In addition, OverloadedStrings is unsound. Library authors can, and do, write unsafe implementations of IsString that cause syntax errors to be caught only at run time instead of at compile time. That is the opposite of one of the most important things we are trying to accomplish by using Haskell instead of, say, some dynamically typed language.
Greg Weber wrote:
You can default a String. So this compiles just fine:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} import Data.Text as T default (T.Text)
No, I do not want string literals to be polymorphic, even if there is some kind of defaulting. I want them to be monomorphic, as they always have been. But I still want to be able to specify to the compiler somehow that the monomorphic type for string literals in a particular module should be something other than String.
Thanks, Yitz
Hi Yitz, I very much agree with you. However, when we complain about something essentially we are asking others to prioritize it ahead of other things. I don't think any more visibility of this issue is going to improve its prioritization. I suspect your only way forward right now is to start implementing something yourself.

Greg Weber wrote:
I very much agree with you. However, when we complain about something essentially we are asking others to prioritize it ahead of other things. I don't think any more visibility of this issue is going to improve its prioritization. I suspect your only way forward right now is to start implementing something yourself.
You're right. But as a professional Haskell developer, I am under the same kinds of deadline pressures as any other professional. So I'm afraid it's not going to be me, at least not in the near future. However, what I can do is raise the red flag. Some people are pushing things in directions which would cause OverloadStrings to become more and more ubiquitous, perhaps even the default. I want to make sure that the people who are doing that are aware of the deep problems with that approach. Sure, as much as anyone else, I want string literals that can be typed as Text. But not at the cost of delaying syntax checking to run time. And, as Bas points out, that there are many different compile time mechanisms that could be used for this. Thanks, Yitz

On Tue, Apr 24, 2012 at 9:26 AM, Yitzchak Gale
Greg Weber wrote:
I very much agree with you. However, when we complain about something essentially we are asking others to prioritize it ahead of other things. I don't think any more visibility of this issue is going to improve its prioritization. I suspect your only way forward right now is to start implementing something yourself.
You're right. But as a professional Haskell developer, I am under the same kinds of deadline pressures as any other professional. So I'm afraid it's not going to be me, at least not in the near future.
However, what I can do is raise the red flag. Some people are pushing things in directions which would cause OverloadStrings to become more and more ubiquitous, perhaps even the default. I want to make sure that the people who are doing that are aware of the deep problems with that approach.
Sure, as much as anyone else, I want string literals that can be typed as Text. But not at the cost of delaying syntax checking to run time.
And, as Bas points out, that there are many different compile time mechanisms that could be used for this.
Thanks, Yitz
Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass: isValidString :: String -> Bool We can give it a default implementation of `const True` for backwards compatibility. Then, whenever GHC applies OverloadedStrings in a case where the type is fully known at compile time (likely the most common case), it can run the check and- if it returns False- stop the compile. This has the benefits of letting existing code continue to work unchanged, and not requiring any Template Haskell to be involved. A downside is that it will still let invalid code through sometimes. Perhaps a solution is to modified the OverloadedStrings extension that requires that the type be fully known. If someone *really* wants polymorphic strings, they can explicitly add `fromString`. I actually think I'd prefer this version. Michael

Michael Snoyman wrote:
Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass: isValidString :: String -> Bool ...whenever GHC applies OverloadedStrings in a case where the type is fully known at compile time (likely the most common case), it can run the check and- if it returns False- stop the compile.
This approach does address the real reason that OverloadedStrings is unsafe in practice: library authors sometimes feel that they must reject certain strings. This gives them a safer outlet for that, with a nice simple API. However, it requires GHC to be able to resolve the monomorphic type of the string literal at a time when it can get its hands on the appropriate isValidString method, already compiled, and call it. Seems like in GHC, at least, the implementation of that would have to involve some kind of TH magic in the background. Is this possible? Thanks, Yitz

On Tue, Apr 24, 2012 at 08:32, Michael Snoyman
Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass:
isValidString :: String -> Bool
If you're going with this approach, why not evaluate the conversion from String immediately? For either case you have to know the monomorphic type, and converting at compile time is more efficient as well. But we're getting pretty close to Template Haskell here. Erik

On Tue, Apr 24, 2012 at 11:36 AM, Erik Hesselink
On Tue, Apr 24, 2012 at 08:32, Michael Snoyman
wrote: Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass:
isValidString :: String -> Bool
If you're going with this approach, why not evaluate the conversion from String immediately? For either case you have to know the monomorphic type, and converting at compile time is more efficient as well. But we're getting pretty close to Template Haskell here.
Erik
I could be mistaken, but I think that would be much harder to implement at the GHC level. GHC would then be responsible for taking a compile-time value and having it available at runtime (i.e., lifting in TH parlance). Of course, I'm no expert on GHC at all, so if someone who actually knows what they're talking about says that this concern is baseless, I agree that your approach is better. Michael

On Tue, Apr 24, 2012 at 10:55, Michael Snoyman
On Tue, Apr 24, 2012 at 11:36 AM, Erik Hesselink
wrote: On Tue, Apr 24, 2012 at 08:32, Michael Snoyman
wrote: Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass:
isValidString :: String -> Bool
If you're going with this approach, why not evaluate the conversion from String immediately? For either case you have to know the monomorphic type, and converting at compile time is more efficient as well. But we're getting pretty close to Template Haskell here.
I could be mistaken, but I think that would be much harder to implement at the GHC level. GHC would then be responsible for taking a compile-time value and having it available at runtime (i.e., lifting in TH parlance). Of course, I'm no expert on GHC at all, so if someone who actually knows what they're talking about says that this concern is baseless, I agree that your approach is better.
But GHC already has all the infrastructure for this, right? You can do exactly this with TH. Erik

On Tue, Apr 24, 2012 at 1:08 PM, Erik Hesselink
On Tue, Apr 24, 2012 at 10:55, Michael Snoyman
wrote: On Tue, Apr 24, 2012 at 11:36 AM, Erik Hesselink
wrote: On Tue, Apr 24, 2012 at 08:32, Michael Snoyman
wrote: Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass:
isValidString :: String -> Bool
If you're going with this approach, why not evaluate the conversion from String immediately? For either case you have to know the monomorphic type, and converting at compile time is more efficient as well. But we're getting pretty close to Template Haskell here.
I could be mistaken, but I think that would be much harder to implement at the GHC level. GHC would then be responsible for taking a compile-time value and having it available at runtime (i.e., lifting in TH parlance). Of course, I'm no expert on GHC at all, so if someone who actually knows what they're talking about says that this concern is baseless, I agree that your approach is better.
But GHC already has all the infrastructure for this, right? You can do exactly this with TH.
Erik
Yes, absolutely. The issue is that TH can be too heavy for both the library author and user: * For the author, you now have to deal with generating some `Q Exp` instead of just producing your data with normal Haskell code. * For the user, you need to replace "foo" with [qqname|foo|]. There's also quite a bit of TH hatred out there, but I'm definitely not in that camp. Nonetheless, I *do* think it would be nice to avoid TH in this case if possible. Michael

On 24/04/2012 11:08, Erik Hesselink wrote:
On Tue, Apr 24, 2012 at 10:55, Michael Snoyman
wrote: On Tue, Apr 24, 2012 at 11:36 AM, Erik Hesselink
wrote: On Tue, Apr 24, 2012 at 08:32, Michael Snoyman
wrote: Here's a theoretically simple solution to the problem. How about adding a new method to the IsString typeclass:
isValidString :: String -> Bool
If you're going with this approach, why not evaluate the conversion from String immediately? For either case you have to know the monomorphic type, and converting at compile time is more efficient as well. But we're getting pretty close to Template Haskell here.
I could be mistaken, but I think that would be much harder to implement at the GHC level. GHC would then be responsible for taking a compile-time value and having it available at runtime (i.e., lifting in TH parlance). Of course, I'm no expert on GHC at all, so if someone who actually knows what they're talking about says that this concern is baseless, I agree that your approach is better.
But GHC already has all the infrastructure for this, right? You can do exactly this with TH.
No, Michael is right. The library writer would need to provide fromString :: String -> Q Exp since there's no way to take an aribtrary value and convert it into something we can compile. Cheers, Simon

On Tue, Apr 24, 2012 at 9:26 AM, Yitzchak Gale
However, what I can do is raise the red flag. Some people are pushing things in directions which would cause OverloadStrings to become more and more ubiquitous, perhaps even the default. I want to make sure that the people who are doing that are aware of the deep problems with that approach.
Sure, as much as anyone else, I want string literals that can be typed as Text. But not at the cost of delaying syntax checking to run time.
What can go wrong when you use an overloaded string to be fromString'd into Text? -- Markus Läll

Markus Läll wrote:
What can go wrong when you use an overloaded string to be fromString'd into Text?
Here's an example: The author of the xml-types package provides an IsString instance for XML names, so you can conveniently represent XML names as string literals in your source code. But not every string is a valid XML name. If you mistype the literal, your program will still compile. It may even run for a while. But when someone uses your program in a way that causes that mistyped XML name literal to be resolved, your program will likely crash, unless you structured it in a way that allows that XML name literal to be wrapped in an appropriate exception handler in the IO monad. -Yitz

I see what you mean -- many libraries provide conveniences like that
(like TagSoups `takeWhile (~== "</a>") tags' and so on). But that's
the inherent mismatch between a String-- a unicode literal --and
whatever else you want it to be, be it ASCII or bash or XML or
something else.. I think the answer to them all is to use TH (as
already suggested :-).
A similar issue is printf, which handles the errors at runtime (though
I think there's a TH solution already existing for that).
On Tue, Apr 24, 2012 at 10:58 AM, Yitzchak Gale
Markus Läll wrote:
What can go wrong when you use an overloaded string to be fromString'd into Text?
Here's an example:
The author of the xml-types package provides an IsString instance for XML names, so you can conveniently represent XML names as string literals in your source code.
But not every string is a valid XML name. If you mistype the literal, your program will still compile. It may even run for a while. But when someone uses your program in a way that causes that mistyped XML name literal to be resolved, your program will likely crash, unless you structured it in a way that allows that XML name literal to be wrapped in an appropriate exception handler in the IO monad.
-Yitz
-- Markus Läll

On Mon, Apr 23, 2012 at 9:58 AM, Yitzchak Gale
In addition, OverloadedStrings is unsound.
No. OverloadedStrings treats string literals as applications of fromString to character list constants. fromString can throw errors, just like fromInteger; this is no less sound than any Haskell function throwing an exception. /g -- "Would you be so kind as to remove the apricots from the mashed potatoes?"

On 23 April 2012 20:34, J. Garrett Morris
On Mon, Apr 23, 2012 at 9:58 AM, Yitzchak Gale
wrote: In addition, OverloadedStrings is unsound.
No. OverloadedStrings treats string literals as applications of fromString to character list constants. fromString can throw errors, just like fromInteger; this is no less sound than any Haskell function throwing an exception.
But it would be safer if those errors were moved to compile time by treating overloaded literals as Template Haskell splices. As in: 1 would be translated to: $(fromIntegerLit 1) where: class FromIntegerLit a where fromIntegerLit :: Integer -> Q (Exp a) (this assumes that Exp is parameterized by the type of the value it splices to which is currently not the case. However you can work around this by using a Proxy or Tagged value.) An instance for Integer is trivial: instance FromIntegerLit Integer where fromIntegerLit = litE . integerL The extra safety comes when giving an instance for natural numbers, for example: newtype Nat = Nat Integer instance FromIntegerLit Nat where fromIntegerLit n | n < 0 = error "Can't have negative Nats" | otherwise = 'Nat `appE` fromIntegerLit n Note that the error will be thrown at compile time when the user has written a negative Nat literal. Regards, Bas

I wrote:
In addition, OverloadedStrings is unsound.
J. Garrett Morris wrote:
fromString can throw errors, just like fromInteger
This is true; the use of polymorphism for numeric literals is also unsound. However, in practice, it is rare for there to be dangerous instances of the numeric type classes.
this is no less sound than any Haskell function throwing an exception.
No. Usually, operations that can throw an exception are in the IO monad, where the specter of a potential exception is more obvious, and where the operation can be wrapped in try or catch. Whereas a string literal that might throw an exception at run time is bizarre, to say the least. And it is extremely difficult to deal with potential exceptions thrown by fundamental language syntax that is sprinkled throughout nearly every Haskell module in existence. Yitz

On Mon, Apr 23, 2012 at 11:10 PM, Yitzchak Gale
This is true; the use of polymorphism for numeric literals is also unsound.
By this logic, head is "unsound", since head [] throws an error. Haskell types are pointed; Haskell computations can diverge. What happens after the computation diverges is irrelevant to type soundness. /g -- "Would you be so kind as to remove the apricots from the mashed potatoes?"

On Tue, Apr 24, 2012 at 02:14, J. Garrett Morris
On Mon, Apr 23, 2012 at 11:10 PM, Yitzchak Gale
wrote: This is true; the use of polymorphism for numeric literals is also unsound.
By this logic, head is "unsound", since head [] throws an error.
Oddly enough, it's actually widely recognized that non-total functions like `head` pose problems. it still remains that string (or indeed numeric) literals are not expected to cause runtime exceptions. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

J. Garrett Morris wrote:
By this logic, head is "unsound", since head [] throws an error. Haskell types are pointed; Haskell computations can diverge.
Well, there are those who would actually agree with that and banish 'head' and friends from the language. But I'll agree with you here. [As an aside - I'm finding that liberal use of Edward's non-empty list type, found in the semigroups package, solves many of those problems for me.] But there are two crucial differences. First, head is just a partial function, not basic language syntax. Second, the divergence of head is constant and well-known, and not dependent on the implementation of a type class at particular types by various library authors.
What happens after the computation diverges is irrelevant to type soundness.
Agreed. I'm not talking about type soundness, in the technical sense. I'm talking about engineering soundness. Thanks, Yitz

I'm not following the details of this thread, but if you guys can come to a conclusion and write up a design, I'd be happy to discuss it. If you want validation of literal strings, then TH quasiquotes are the way to go: [url| http://this/that |] will let you specify the parser/validator to use ("url" in this case) and allow any error messages to be delivered in a civilised way at compile time. I don't really want to make "http://this/that" have exactly this semantics; apart from anything else, which parser do you mean. This is what TH quasiquotation is *for*. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell- | users-bounces@haskell.org] On Behalf Of Yitzchak Gale | Sent: 24 April 2012 07:46 | To: J. Garrett Morris | Cc: GHC users | Subject: Re: default instance for IsString | | J. Garrett Morris wrote: | > By this logic, head is "unsound", since head [] throws an error. | > Haskell types are pointed; Haskell computations can diverge. | | Well, there are those who would actually agree with that and banish 'head' | and friends from the language. | But I'll agree with you here. | | [As an aside - I'm finding that liberal use of Edward's non-empty list type, | found in the semigroups package, solves many of those problems for me.] | | But there are two crucial differences. First, head is just a partial | function, not basic language syntax. | Second, the divergence of head is constant and well-known, and not dependent | on the implementation of a type class at particular types by various library | authors. | | > What happens after the computation diverges is irrelevant to type | > soundness. | | Agreed. I'm not talking about type soundness, in the technical sense. I'm | talking about engineering soundness. | | Thanks, | Yitz | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon Peyton-Jones wrote:
If you want validation of literal strings, then TH quasiquotes are the way to go:
I agree. OverloadedStrings is, in effect, an unsafe replacement for quasiquotes. People find OverloadedStrings easier to use than quasiquotes, so its use in that way is becoming popular. What we need is a mechanism for allowing string literals to have the type Text or ByteString instead of String. I do not want to be forced to turn on UnsafeQuasiQuotes every time I need a string literal. So in my opinion, OverloadedStrings is the wrong mechanism for providing Text and ByteString literals. Alternatives that have been suggested: o A hard-coded pragma to specify the type of string literals in a module as Text or ByteString. o An extra method of IsString, of type QuasiQuoter, that runs at compile time in a monomorphic context. o As above, but only check syntax at compile time in a monomorphic context. That allows a simpler API, without requiring any TH knowledge in most cases. Thanks, Yitz

You do know, that you already *can* have safe Text and ByteString from
an overloaded string literal.
On Tue, Apr 24, 2012 at 11:46 AM, Yitzchak Gale
Simon Peyton-Jones wrote:
If you want validation of literal strings, then TH quasiquotes are the way to go:
I agree. OverloadedStrings is, in effect, an unsafe replacement for quasiquotes. People find OverloadedStrings easier to use than quasiquotes, so its use in that way is becoming popular.
What we need is a mechanism for allowing string literals to have the type Text or ByteString instead of String.
I do not want to be forced to turn on UnsafeQuasiQuotes every time I need a string literal. So in my opinion, OverloadedStrings is the wrong mechanism for providing Text and ByteString literals.
Alternatives that have been suggested:
o A hard-coded pragma to specify the type of string literals in a module as Text or ByteString.
o An extra method of IsString, of type QuasiQuoter, that runs at compile time in a monomorphic context.
o As above, but only check syntax at compile time in a monomorphic context. That allows a simpler API, without requiring any TH knowledge in most cases.
Thanks, Yitz
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Markus Läll

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

On Tue, Apr 24, 2012 at 12:35 PM, Yitzchak Gale
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@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

But if you want a string to be, say, an XML document then you want to
turn the string literal into an XML syntax tree (which is correct by
the definition of the data types representing it). As this conversion
can fail (all unicode strings are not valid representations of an XML
syntax tree), you need to compile-time parse it. As you will need a
compile-time parser for all such languages, then TH is the only
reasonable choice -- or isn't it?
On Tue, Apr 24, 2012 at 12:35 PM, Yitzchak Gale
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
-- Markus Läll

Why are potentially partial literals scarier than the fact that every value
in the language could lead to an exception when forced?
On Tue, Apr 24, 2012 at 5:35 AM, Yitzchak Gale
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 24/04/2012 14:14, Daniel Peebles wrote:
Why are potentially partial literals scarier than the fact that every value in the language could lead to an exception when forced?
My thoughts exactly. In this thread people are using the term "safe" to mean "total". We already overload "safe" too much, might it be a better idea to use "total" instead? (and FWIW I'm not sure I see what all the fuss is about either) Cheers, Simon
On Tue, Apr 24, 2012 at 5:35 AM, Yitzchak Gale
mailto:gale@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@haskell.org mailto:Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon Marlow wrote:
In this thread people are using the term "safe" to mean "total". We already overload "safe" too much, might it be a better idea to use "total" instead?
I'm not sure what you're talking about. I don't see how this thread has anything to do with total vs. partial functions. I'm saying that the static syntax of string literals should be checked at compile time, not at run time. Isn't that simple enough, and self-evident? Thanks, Yitz

On 24/04/2012 15:19, Yitzchak Gale wrote:
Simon Marlow wrote:
In this thread people are using the term "safe" to mean "total". We already overload "safe" too much, might it be a better idea to use "total" instead?
I'm not sure what you're talking about. I don't see how this thread has anything to do with total vs. partial functions.
My apologies if I've misunderstood, but the problem that people seem to be worried about is fromString failing at runtime (i.e. it is a partial function), and this has been referred to as "unsafe".
I'm saying that the static syntax of string literals should be checked at compile time, not at run time. Isn't that simple enough, and self-evident?
Well, the syntax of overloaded integers isn't checked at compile time, so why should strings be special? I'm not arguing in favour of using OverloadedStrings for URLs or anything like that, but I'm not sure I see why it's bad for Text and ByteString. Cheers, Simon

Hi Simon, First of all, I'm sorry if I'm coming off as too combative, as Greg says. That is certainly not my intention. I'm not asking for any free work from you, either. 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. If it's really important to use this mechanism for typing string literals as Text and ByteString, how about this: Create a new class IsBuiltinString, with method isBuiltinString. Make it hidden so that no new instances can be defined outside of base, and provide instances only for String, Text, and ByteString, for now. Then I will happily use the OverloadedBuiltinStrings extension. People who don't see any problem with OverloadedStrings can go on using it as before. Thanks, Yitz

On Wed, Apr 25, 2012 at 10:15, 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.
I don't think IsString should be dismissed so easily. I agree that instances should be total functions (and I don't like the ByteString.Char8 instance for that reason) but there are many more good use cases than Text and (UTF8) ByteStrings. For example, we have a couple of newtypes over Text that do different kinds of normalization. An IsString instance for these is useful and total. Erik

Erik Hesselink wrote:
I don't think IsString should be dismissed so easily.
I'm just saying I don't want to be forced to use it. If others like it, I'm not dismissing it.
we have a couple of newtypes over Text that do different kinds of normalization. An IsString instance for these is useful and total.
True. Perhaps you'd be able to get IsBuiltinString instances for those too, using newtype deriving, if only the method names of IsBuiltinString are hidden and the class name is exported. If that doesn't work, I'm fine with using a quasiquoter for those instead. Or even just the usual newtype unwrapping and wrapping. And again, if you provide IsString and others want to use it, that's fine. Thanks, Yitz

Hi, On 04/25/2012 09:15 AM, Yitzchak Gale wrote:
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.
But the problem here is that reasonable people may choose to disagree as to what is ill-advised or not. Thus, rather than generalising the existing approach to overloaded literals in the most straightforward way possible to strings, the argument is that overloaded string literals need to be handled differently due to a fundamentally subjective argument about what is ill-advised or not, and how overloaded strings might be "abused" unless there is some special checking in place. I'm not saying that partial instances of "fromString" is a good idea. In fact, I'm prepared to believe those who say that all instances of this they have come across are ill-advised. But that is not to say that it necessarily always has to be a bad idea. Thus, it seems to me that a systematic language extension is preferable for simplicity and as it does not add any fundamentally new issues, to one which leads to a more involved design based on subjective arguments about programming style. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk

On April 25, 2012 04:15:41 Yitzchak Gale wrote:
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.
Maybe what you really want is the ability to control instance imports? Is there a technical reason this couldn't be done? The Haskell report only says doing this is not part of haskell. It doesn't say why. Cheers! -Tyson

On Wed, Apr 25, 2012 at 8:19 AM, Tyson Whitehead
Is there a technical reason this couldn't be done? The Haskell report only says doing this is not part of haskell. It doesn't say why.
I think the problem is incoherence, what if the same Map value got used with two different instances of Int? -- Johan

On April 25, 2012 12:20:16 Johan Tibell wrote:
On Wed, Apr 25, 2012 at 8:19 AM, Tyson Whitehead
wrote: Is there a technical reason this couldn't be done? The Haskell report only says doing this is not part of haskell. It doesn't say why.
I think the problem is incoherence, what if the same Map value got used with two different instances of Int?
I'm not sure I follow how allowing control over importing of instances could allow a programmer to define multiple instances for the same types. I would have expected this to result in a link time error as a product of multiple declerations (something like a multiple symbol definition) regardless of whether any module brings it into scope as a possible candidate for use. Cheers! -Tyson

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.
Could you name some names here? Regardless of how this whole thread goes, maybe people will agree that those uses were indeed ill-advised, and we can get them fixed up. Perhaps the problem is that fromString is very easy to understand and write, but quasi-quoters sound like a whole new complicated thing to learn about. If we could either demonstrate that they're not so bad to write, or have a little library that makes them easier for "stringlike" things, then maybe we could move the first instinct away from "hack a quick fromString" to "hack a quick QQ".

Hi, 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). Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

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@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

Daniel Peebles wrote:
Why are potentially partial literals scarier than the fact that every value in the language could lead to an exception when forced?
That's a legitimate question, but it's strange to hear it from you. People ask that same question about Haskell's static type system. Why bother? Every value could lead to an exception when forced. So we might as well check everything at run time. Wouldn't it be ironic if the one thing that every language other than Haskell is able to check at compile time, namely the static syntax of string literals, could only be checked at run time in Haskell? Especially when, with just a little care, we could easily continue to check it at compile time while still supporting string literals of type Text and ByteString. I guess I'm just not understanding your question. Thanks, Yitz

Hi, Yitzhack Gale wrote:
Wouldn't it be ironic if the one thing that every language other than Haskell is able to check at compile time, namely the static syntax of string literals, could only be checked at run time in Haskell?
I don't really see the irony, I'm afraid, as nothing really has changed, and as Simon M. that I don't see what the fuss is about. Presumably, the syntax of string literals as such is still going to be checked by the scanner, as it always was? And the issue, then, is whether an overloaded "fromString" is total in all its overloadings? Or did I miss something central, here? Well, Haskell is not a total language, so the fact that "fromString" might have non-total overloadings is not surprising. Yes, "fromString" would be implicitly inserted, just like e.g. "fromInteger" for overloaded integer literals, to create the effect of overloaded literals, but this is really just a convenience, albeit an important one. The benefit of an approach to overloading of string literals that is analogous to the existing method for overloading of numeric literals would seem to me to outweigh the benefits of additional static checking through an essentially new approach to overloading of literals for a specific case. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk

From what I can see the core of the disagreement is that some people believe fromString will tempt misuse (i.e. using *easily* partial functions, like XML validation), while others don't think it's that likely. Indeed misusing IsString is worse than your average partial function because of the global nature of typeclasses and fromString being implicit. If that is indeed the core of the disagreement, then can we at least agree that writing a partial fromString is a bad idea? I'd say *easily* partial since someone pointed out the UTF8 fromString is partial, but it's pretty hard to type bad UTF8 accidentally so it doesn't seem so bad to me.
If we agree that 'fromString :: String -> XML' is a bad idea, then can
we just say "so don't do that then"? Safety is good but there's a
point where you have to trust people with the sharp tools. Suppose a
library author adding a fromString for regexes that crashes on
unbalanced parens. If it's a problem in practice I imagine people
would complain to them to change their library, or use another
library.
On Tue, Apr 24, 2012 at 9:10 AM, Henrik Nilsson
Hi,
Yitzhack Gale wrote:
Wouldn't it be ironic if the one thing that every language other than Haskell is able to check at compile time, namely the static syntax of string literals, could only be checked at run time in Haskell?
I don't really see the irony, I'm afraid, as nothing really has changed, and as Simon M. that I don't see what the fuss is about.
Presumably, the syntax of string literals as such is still going to be checked by the scanner, as it always was? And the issue, then, is whether an overloaded "fromString" is total in all its overloadings? Or did I miss something central, here?
Well, Haskell is not a total language, so the fact that "fromString" might have non-total overloadings is not surprising. Yes, "fromString" would be implicitly inserted, just like e.g. "fromInteger" for overloaded integer literals, to create the effect of overloaded literals, but this is really just a convenience, albeit an important one.
The benefit of an approach to overloading of string literals that is analogous to the existing method for overloading of numeric literals would seem to me to outweigh the benefits of additional static checking through an essentially new approach to overloading of literals for a specific case.
Best,
/Henrik
-- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I think my point was more along the lines that every *value*, regardless of
whether it's a function or not, can be partial (ignoring primitive types
and such). I can hand you a list where the third Int in it will cause you
to crash if you force it.
In that sense, whether every numeric literal expands to fromInteger ... or
every string literal expands to fromString ... doesn't really make it any
different from any other value. Is the concern that because it's
polymorphic, that different uses of the "same" polymorphic value might or
might not crash? That's the case for any polymorphic value: take e.g., read
"()", which will crash or not depending on where it's used. If it's just
the case that the value itself could crash when forced, well, that's true
of any value of any lifted type.
So if every value, when forced, can crash your program, possibly depending
on what type it's instantiated to, why are we so concerned about String
literals behaving like everything else?
Dan
On Tue, Apr 24, 2012 at 1:23 PM, Evan Laforge
From what I can see the core of the disagreement is that some people believe fromString will tempt misuse (i.e. using *easily* partial functions, like XML validation), while others don't think it's that likely. Indeed misusing IsString is worse than your average partial function because of the global nature of typeclasses and fromString being implicit. If that is indeed the core of the disagreement, then can we at least agree that writing a partial fromString is a bad idea? I'd say *easily* partial since someone pointed out the UTF8 fromString is partial, but it's pretty hard to type bad UTF8 accidentally so it doesn't seem so bad to me.
If we agree that 'fromString :: String -> XML' is a bad idea, then can we just say "so don't do that then"? Safety is good but there's a point where you have to trust people with the sharp tools. Suppose a library author adding a fromString for regexes that crashes on unbalanced parens. If it's a problem in practice I imagine people would complain to them to change their library, or use another library.
On Tue, Apr 24, 2012 at 9:10 AM, Henrik Nilsson
wrote: Hi,
Yitzhack Gale wrote:
Wouldn't it be ironic if the one thing that every language other than Haskell is able to check at compile time, namely the static syntax of string literals, could only be checked at run time in Haskell?
I don't really see the irony, I'm afraid, as nothing really has changed, and as Simon M. that I don't see what the fuss is about.
Presumably, the syntax of string literals as such is still going to be checked by the scanner, as it always was? And the issue, then, is whether an overloaded "fromString" is total in all its overloadings? Or did I miss something central, here?
Well, Haskell is not a total language, so the fact that "fromString" might have non-total overloadings is not surprising. Yes, "fromString" would be implicitly inserted, just like e.g. "fromInteger" for overloaded integer literals, to create the effect of overloaded literals, but this is really just a convenience, albeit an important one.
The benefit of an approach to overloading of string literals that is analogous to the existing method for overloading of numeric literals would seem to me to outweigh the benefits of additional static checking through an essentially new approach to overloading of literals for a specific case.
Best,
/Henrik
-- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

So if every value, when forced, can crash your program, possibly depending on what type it's instantiated to, why are we so concerned about String literals behaving like everything else?
Well, that was exactly my point. Some people think it's *more likely* that people will write crashing fromString methods.

I'm the one arguing in defense of the current state of
OverloadedStrings, and no secret that Yitz has been the main opponent
of it.
For what I understand, and putting words in his mouth, he wants to
write `"

On 4/24/12 3:35 PM, Markus Läll wrote:
For what I understand, and putting words in his mouth, he wants to write `"
" :: XML' and have the compiler tell him at compile-time that this is not valid XML (if it actually is, imagine that there's something invalid between the double quotes). I.e he wants to parse the string at compile-time and have the compilation fail if the parse fails, or have the string literal be replaced by the syntax tree of that XML if it succeeds.* This example is meta-programming par excellence, which is what Template Haskell is for -- use it.
Indeed. Asking that "illegal" string literals be caught at compile time is, in effect, updating the syntax of Haskell itself. As it stands, Haskell has a definition of what a string literal is (see the Report), and whether or not that literal can be successfully coerced into a given type is neither here nor there; just as for numeric literals. I'm all for static-checking. (Even moreso with every passing year.) But if you want to make up new sorts of literals and have them checked for validity, that's exactly what quasiquotes are there for. Since you are altering the syntax of Haskell, rather than accepting what Haskell calls strings, then this is metaprogramming and so you're going to need TH, QQ, or some similar metaprogramming facility. Whereas for ByteString and Text the goal is specifically to serve as an efficient/correct replacement for String; thus, overloading string literals to support those types is _not_ asking to change the syntax of Haskell. 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. -- Live well, ~wren

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!

One can always use a Maybe to make an IsString literal total. Perhaps this
is what library authors should do in those cases when a fromString
implementation is obviously partial.
i.e. instead of instance IsString XML where ...
define: instance IsString (Maybe XML) where ...
HTH,
Ozgur
On 24 April 2012 15:03, Yitzchak Gale
Daniel Peebles wrote:
Why are potentially partial literals scarier than the fact that every value in the language could lead to an exception when forced?
That's a legitimate question, but it's strange to hear it from you.
People ask that same question about Haskell's static type system. Why bother? Every value could lead to an exception when forced. So we might as well check everything at run time.
Wouldn't it be ironic if the one thing that every language other than Haskell is able to check at compile time, namely the static syntax of string literals, could only be checked at run time in Haskell? Especially when, with just a little care, we could easily continue to check it at compile time while still supporting string literals of type Text and ByteString.
I guess I'm just not understanding your question.
Thanks, Yitz

On Wed, Apr 25, 2012 at 11:39 AM, Ozgur Akgun
One can always use a Maybe to make an IsString literal total. Perhaps this is what library authors should do in those cases when a fromString implementation is obviously partial.
i.e. instead of instance IsString XML where ... define: instance IsString (Maybe XML) where ...
HTH, Ozgur
This sounds sensible, but then you'll have to handle the Nothing case of the Maybe. There you are, writing a literal, and also writing fallback code specifying what should be done in case you messed up when writing the literal. What can you reasonably write there, other than error "oops, I wrote a bad literal"? You're back where you started. There's not much you can do about programmer error at runtime except abort, which is why you'd really prefer to have it checked at compile time. But unless you write a quasiquoter, runtime checking might be your only option, and at that point whether you prefer convenience or explicitness seems like a question of taste, because the important bad thing (runtime assertions) you're already stuck with.

The defaulting is very good for most use cases, however I am
discovering it won't default when I try to build up a list or tuple.
This does not work:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleInstances #-}
module Default (noDefault) where
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 8:31 PM, Greg Weber
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (23)
-
Albert Y. C. Lai
-
Bas van Dijk
-
Brandon Allbery
-
Brent Yorgey
-
Christopher Done
-
Daniel Peebles
-
Erik Hesselink
-
Evan Laforge
-
Greg Weber
-
Gábor Lehel
-
Henrik Nilsson
-
J. Garrett Morris
-
Jeremy Shaw
-
Joachim Breitner
-
Johan Tibell
-
Markus Läll
-
Michael Snoyman
-
Ozgur Akgun
-
Simon Marlow
-
Simon Peyton-Jones
-
Tyson Whitehead
-
wren ng thornton
-
Yitzchak Gale