Re: default instance for IsString

2012-04-24 Thread Albert Y. C. Lai

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!

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Potential GSoC proposal: Reduce the speed gap between 'ghc -c' and 'ghc --make'

2012-04-24 Thread Evan Laforge
> Thank you for the answer.
> I'll be working on another project during the summer, but I'm still
> interested in making interface files load faster.
>
> The idea that I currently like the most is to make it possible to save
> and load objects in the "GHC heap format". That way, deserialisation
> could be done with a simple fread() and a fast pointer fixup pass,
> which would hopefully make running many 'ghc -c' processes as fast as
> a single 'ghc --make'. This trick is commonly employed in the games
> industry to speed-up load times [1]. Given that Haskell is a
> garbage-collected language, the implementation will be trickier than
> in C++ and will have to be done on the RTS level.
>
> Is this a good idea? How hard it would be to implement this optimisation?
>
> Another idea (that I like less) is to implement a "build server" mode
> for GHC. That way, instead of a single 'ghc --make' we could run
> several ghc build servers in parallel. However, Evan Laforge's efforts
> in this direction didn't bring the expected speedup. Perhaps it's
> possible to improve on his work.

I don't know if this would help, but I remember during Rob Pike's
initial go talk he described how the 8g compiler could be so fast.  I
don't remember the exact details, but it was something to the effect
that interface files would embed the interfaces of their depends, so
this way the compiler only need read the direct imports, not the
transitive dependency.

Of course this might not work so well with ghc's fat interfaces with
lots of inlined code, but it's a thought.  One of the only impressive
things that impressed me about go was the compilation speed, but that
was quite impressive.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Potential GSoC proposal: Reduce the speed gap between 'ghc -c' and 'ghc --make'

2012-04-24 Thread Mikhail Glushenkov
Hello Simon,

Sorry for the delay.

On Tue, Apr 10, 2012 at 1:03 PM, Simon Marlow  wrote:
>
>> Questions:
>>
>> Would implementing this optimisation be a worthwhile/realistic GSoC
>> project?
>> What are other potential ways to bring 'ghc -c' performance up to par
>> with 'ghc --make'?
>
>
> My guess is that this won't have a significant impact on ghc -c compile
> times.
>
> The advantage of squashing the .hi files for a package together is that they
> could share a string table, which would save a bit of space and time, but I
> think the time saved is small compared to the cost of deserialising and
> typechecking the declarations from the interface, which still has to be
> done.  In fact it might make things worse, if the string table for the whole
> base package is larger than the individual tables that would be read from
> .hi files.  I don't think mmap() will buy very much over the current scheme
> of just reading the file into a ByteArray.

Thank you for the answer.
I'll be working on another project during the summer, but I'm still
interested in making interface files load faster.

The idea that I currently like the most is to make it possible to save
and load objects in the "GHC heap format". That way, deserialisation
could be done with a simple fread() and a fast pointer fixup pass,
which would hopefully make running many 'ghc -c' processes as fast as
a single 'ghc --make'. This trick is commonly employed in the games
industry to speed-up load times [1]. Given that Haskell is a
garbage-collected language, the implementation will be trickier than
in C++ and will have to be done on the RTS level.

Is this a good idea? How hard it would be to implement this optimisation?

Another idea (that I like less) is to implement a "build server" mode
for GHC. That way, instead of a single 'ghc --make' we could run
several ghc build servers in parallel. However, Evan Laforge's efforts
in this direction didn't bring the expected speedup. Perhaps it's
possible to improve on his work.

[1] 
http://www.gamasutra.com/view/feature/132376/delicious_data_baking.php?print=1
-- 
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread wren ng thornton

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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Evan Laforge
> 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.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Markus Läll
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 `"" :: 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.

If I have a correct understanding of what Yitz has in mind, then this
is why *I'm* having this argument. In all due respect, Yitz, correct
me if I've got something wrong!


* Parsing is a partial function.

-- 
Markus Läll

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Daniel Peebles
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  wrote:

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


Re: default instance for IsString

2012-04-24 Thread 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
> n...@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


Re: default instance for IsString

2012-04-24 Thread 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
n...@cs.nott.ac.uk

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Simon Marlow

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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Yitzchak Gale
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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Simon Marlow

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:g...@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

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



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Simon Marlow

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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Daniel Peebles
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  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
> 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


Re: default instance for IsString

2012-04-24 Thread Michael Snoyman
On Tue, Apr 24, 2012 at 1:08 PM, 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.
>
> 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: trouble building ghc-7.4 on Fedora 18 (devel) ARM

2012-04-24 Thread Joachim Breitner
Hi,

Am Dienstag, den 24.04.2012, 19:50 +0900 schrieb Jens Petersen:
> >- debian/patches/armhf_llvm_abi: Pass -float-abi=hard to llc on armhf if
> >  __ARM_PCS_VFP is defined (needs to be preprocessed for this)
> >- debian/rules: Define __ARM_PCS_VFP on armhf for the above patch.
> >
> > you might need to set __ARM_PCS_VFP. This is the code in debian/rules:
> 
> Thanks Joachim for catching this!
> 
> Hmm, perhaps I am being really stupid, but even after that
> the build still fails in exactly the same way.  I am kind of stumped...
> 
> http://arm.koji.fedoraproject.org/koji/getfile?taskID=755369&name=build.log
> http://arm.koji.fedoraproject.org/koji/taskinfo?taskID=755369
> 
> (the armv5tel seems to be ok so far afaict)

no idea, but I’m CC’ing people knowing more about the ARM port (Karel
and Jani), maybe they can help you.

Greetings,
Joachim

-- 
Joachim "nomeata" Breitner
Debian Developer
  nome...@debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nome...@joachim-breitner.de | http://people.debian.org/~nomeata


signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Markus Läll
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  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



-- 
Markus Läll

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: trouble building ghc-7.4 on Fedora 18 (devel) ARM

2012-04-24 Thread Jens Petersen
>    - debian/patches/armhf_llvm_abi: Pass -float-abi=hard to llc on armhf if
>      __ARM_PCS_VFP is defined (needs to be preprocessed for this)
>    - debian/rules: Define __ARM_PCS_VFP on armhf for the above patch.
>
> you might need to set __ARM_PCS_VFP. This is the code in debian/rules:

Thanks Joachim for catching this!

Hmm, perhaps I am being really stupid, but even after that
the build still fails in exactly the same way.  I am kind of stumped...

http://arm.koji.fedoraproject.org/koji/getfile?taskID=755369&name=build.log
http://arm.koji.fedoraproject.org/koji/taskinfo?taskID=755369

(the armv5tel seems to be ok so far afaict)

Jens

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread 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


Re: default instance for IsString

2012-04-24 Thread Markus Läll
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  wrote:
> 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread 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.
>
> 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread 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


Re: default instance for IsString

2012-04-24 Thread 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Markus Läll
I see what you mean -- many libraries provide conveniences like that
(like TagSoups `takeWhile (~== "") 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  wrote:
> 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: default instance for IsString

2012-04-24 Thread Simon Peyton-Jones
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-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@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



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Markus Läll
On Tue, Apr 24, 2012 at 9:26 AM, Yitzchak Gale  wrote:
> 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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: default instance for IsString

2012-04-24 Thread Yitzchak Gale
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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users