Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bryan O'Sullivan
On Sat, Aug 14, 2010 at 10:46 PM, Michael Snoyman mich...@snoyman.comwrote:


 When I'm writing a web app, my code is sitting on a Linux system where the
 default encoding is UTF-8, communicating with a database speaking UTF-8,
 receiving request bodies in UTF-8 and sending response bodies in UTF-8. So
 converting all of that data to UTF-16, just to be converted right back to
 UTF-8, does seem strange for that purpose.


Bear in mind that much of the data you're working with can't be readily
trusted. UTF-8 coming from the filesystem, the network, and often the
database may not be valid. The cost of validating it isn't all that
different from the cost of converting it to UTF-16.

And of course the internals of Data.Text are all fusion-based, so much of
the time you're not going to be allocating UTF-16 arrays at all, but instead
creating a pipeline of characters that are manipulated in a tight loop. This
eliminates a lot of the additional copying that bytestring has to do, for
instance.

To give you an idea of how competitive Data.Text can be compared to C code,
this is the system's wc command counting UTF-8 characters in a modestly
large file:

$ time wc -m huge.txt
32443330
real 0.728s


This is Data.Text performing the same task:

$ time ./FileRead text huge.txt
32443330
real 0.697s
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Donn Cave
Quoth John Millikin jmilli...@gmail.com,

 I don't see why [Char] is obvious -- you'd never use [Word8] for
 storing binary data, right? [Char] is popular because it's the default
 type for string literals, and due to simple inertia, but when there's
 a type based on packed arrays there's no reason to use the list
 representation.

Well, yes, string literals - and pattern matching support, maybe
that's the same thing.  And I think it's fair to say that [Char]
is a natural, elegant match for the language, I mean it leverages
your basic Haskell skills if for example you want to parse something
fairly simple.  So even if ByteString weren't the monumental hassle
it is today for simple stuff, String would have at least a little appeal.
And if packed arrays really always mattered, [Char] would be long gone.
They don't, you can do a lot of stuff with [Char] before it turns into
a problem.

 Also, despite the name, ByteString and Text are for separate purposes.
 ByteString is an efficient [Word8], Text is an efficient [Char] -- use
 ByteString for binary data, and Text for...text. Most mature languages
 have both types, though the choice of UTF-16 for Text is unusual.

Maybe most mature languages have one or more extra string types
hacked on to support wide characters.  I don't think it's necessarily
a virtue.  ByteString vs. ByteString.Char8, where you can choose
more or less indiscriminately to treat the data as Char or Word8,
seems to me like a more useful way to approach the problem.  (Of
course, ByteString.Char8 isn't a good way to deal with wide characters
correctly, I'm just saying that's where I'd like to find the answer,
not in some internal character encoding into which all text data
must be converted.)

Donn Cave, d...@avvanta.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bryan O'Sullivan
On Sat, Aug 14, 2010 at 10:07 PM, Donn Cave d...@avvanta.com wrote:


 Am I confused about this?  It's why I can't see Text ever being

simply the obvious choice.  [Char] will continue to be the obvious
 choice if you want a functional data type that supports pattern
 matching etc.


Actually, with view patterns, Text is pretty nice to pattern match against:

foo (uncons - Just (c,cs)) = whee

despam (prefixed spam - Just suffix) = whee `mappend` suffix

ByteString will continue to be the obvious choice
 for big data loads.


Don't confuse I have big data with I need bytes. If you are working with
bytes, use bytestring. If you are working with text, outside of a few narrow
domains you should use text.

 We'll have a three way choice between programming
 elegance, correctness and efficiency.  If Haskell were more than
 just a research language, this might be its most prominent open
 sore, don't you think?


No, that's just FUD.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Colin Paul Adams
 Bryan == Bryan O'Sullivan b...@serpentine.com writes:

Bryan On Sat, Aug 14, 2010 at 10:46 PM, Michael Snoyman 
mich...@snoyman.com wrote:
Bryan When I'm writing a web app, my code is sitting on a Linux
Bryan system where the default encoding is UTF-8, communicating
Bryan with a database speaking UTF-8, receiving request bodies in
Bryan UTF-8 and sending response bodies in UTF-8. So converting all
Bryan of that data to UTF-16, just to be converted right back to
Bryan UTF-8, does seem strange for that purpose.


Bryan Bear in mind that much of the data you're working with can't
Bryan be readily trusted. UTF-8 coming from the filesystem, the
Bryan network, and often the database may not be valid. The cost of
Bryan validating it isn't all that different from the cost of
Bryan converting it to UTF-16.

But UTF-16 (apart from being an abomination for creating a hole in the
codepoint space and making it impossible to ever etxend it) is slow to
process compared with UTF-32 - you can't get the nth character in
constant time, so it seems an odd choice to me.
-- 
Colin Adams
Preston Lancashire
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Johan Tibell
Hi Colin,

On Sun, Aug 15, 2010 at 9:34 AM, Colin Paul Adams
co...@colina.demon.co.ukwrote:

 But UTF-16 (apart from being an abomination for creating a hole in the
 codepoint space and making it impossible to ever etxend it) is slow to
 process compared with UTF-32 - you can't get the nth character in
 constant time, so it seems an odd choice to me.


Aside: Getting the nth character isn't very useful when working with Unicode
text:

* Most text processing is linear.
* What we consider a character and what Unicode considers a character
differs a bit e.g. since Unicode uses combining characters.

Cheers,
Johan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Ivan Lazar Miljenovic
Don Stewart d...@galois.com writes:

 * Pay attention to Haskell Cafe announcements
 * Follow the Reddit Haskell news.
 * Read the quarterly reports on Hackage
 * Follow Planet Haskell

And yet there are still many packages that fall under the radar with no
announcements of any kind on initial release or even new versions :(

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor) (Again)

2010-08-15 Thread Ivan Lazar Miljenovic
Alexey Karakulov ankaraku...@gmail.com writes:

  (Ord b) must be deduced from (Functor (Set b)) but it doesn't. I
  don't know whether it's my mistake somewhere or ghc problem.

 I've come across this problem as well; the best solution I've seen so
 far is the one taken by Ganesh in his rmonad library:
 http://hackage.haskell.org/package/rmonad

 Thanks for the link, but RFunctor typeclass is still (more or less)
 polymorphic, so I couldn't write ByteString instance for it. (Really I don't
 care about ByteString, but it's good example). However, I could try to use
 Suitable+Constraints concept for non-polymorphic functors.

Yeah, I'm working on something like this at the moment, but I'm
currently stuck on naming: if I want to have Functor for kind * - *,
what's a good name for a type class for kind *?

Also, is there any type for which having a map a - a _doesn't_ make
sense?  Bloomfilters maybe?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Ertugrul Soeylemez
Conal Elliott co...@conal.net wrote:

 On Sat, Aug 14, 2010 at 9:27 AM, Ertugrul Soeylemez e...@ertes.de wrote:

  Conal Elliott co...@conal.net wrote:
 
There are various models.  One (the state monad model) of them
would desugar this to:
   
 \world0 -
 let (x, world1) = getLine world0
 world2 = print (x+1) world1
 world3 = print (x+2) world2
 in world3
  
   This state monad model does not really work for IO, since it fails
   to capture IO's concurrency (with non-deterministic interleaving).
 
  Well, it does capture concurrency and FFI, but it has no explicit
  notion for it.  In other words, concurrent threads and FFI calls are
  effects like everything else, so the forkIO function just changes
  the world state implicitly and that's it.

 Consider that IO's concurrency means that something else can happen
 between printing x+1 and printing x+2, so that x+2 is *not* printed in
 world2, but rather in a world influenced outside of this thread.
 Similarly, x+1 might not be printed in world1, and the getLine might
 not be executed in world0.  So World - (a, World) is *not* expressive
 enough to explain Haskell-IO-style concurrency.

 Do you see what I mean?

I don't agree.  A concurrent change is the effect of an IO action, not
of the thread.  For example if a concurrent thread writes to an MVar,
then that change becomes the effect of the next takeMVar, which gets
executed.  If a concurrent thread changes a file on disk, then that
changing becomes the effect of the next readFile, which reads the
changed file.

As said, the state monad model captures concurrency, but has no explicit
notion for it.  It captures it as an effect just like every other.


   I don't know whether/how the EDSL model you mention addresses
   concurrency or FFI.
 
  Just like the state monad model.  This is not a weakness of the
  interpretation, but of the IO monad itself, because it is quite a
  raw and straightforward language for doing I/O.

 And the IO monad is what Jerzy asked about.  I'm pointing out that the
 state monad does not capture concurrency, and the EDSL model does
 not capture FFI.  (Really, it depends which EDSL model.  I haven't
 seen one that can capture FFI.  And maybe not concurrency either.)

The EDSL model is just an imperative language inside of Haskell.  It
captures thread launching as an action and concurrent changes as
actions.  Just as well it does capture FFI calls as actions, and so on.

Maybe you have some notion of capturing other than being able to
express.  Maybe by capturing you mean being able to express the
particular concept/construct in the type system.  But then the IO monad
doesn't even capture writing to a file handle.  Or maybe you're talking
about elegance.  I don't really know.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor) (Again)

2010-08-15 Thread Stephen Tetley
On 15 August 2010 08:50, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:

 Yeah, I'm working on something like this at the moment, but I'm
 currently stuck on naming: if I want to have Functor for kind * - *,
 what's a good name for a type class for kind *?

Conor McBride has suggested looking at arity families of functor-like
things (functor, traversable, foldable, halfzippable(?)) may be
worthwhile:

http://www.haskell.org/pipermail/haskell-cafe/2008-June/044011.html

Functors and bi-functors have obvious names, but naming zero arity and
three-and-higher ones would need systematic treatment.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor) (Again)

2010-08-15 Thread Alexey Karakulov
On Sun, Aug 15, 2010 at 10:50 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

Yeah, I'm working on something like this at the moment, but I'm
 currently stuck on naming: if I want to have Functor for kind * - *,
 what's a good name for a type class for kind *?


I was thinking about EtaFunctor, which stands for η-expanded Functor. But
I'm not sure about η-expansion is correct term for removing polymorphism
from the type class.

Also, is there any type for which having a map a - a _doesn't_ make
 sense?  Bloomfilters maybe?


Not the answer, but there are cases where having a map (a - b) - f - g
could make some new sense:

data BitList = ...
fromBoolList :: [Bool] - BitList
type instance NewPt [a] b = [b]
type instance NewPt [a] Bool = BitList

But this kind of overlapping type instance is not allowed in ghc (yet?)

-- 
All the best,
Alexey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Vo Minh Thu
2010/8/15 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Don Stewart d...@galois.com writes:

     * Pay attention to Haskell Cafe announcements
     * Follow the Reddit Haskell news.
     * Read the quarterly reports on Hackage
     * Follow Planet Haskell

 And yet there are still many packages that fall under the radar with no
 announcements of any kind on initial release or even new versions :(

If you're interested in a comprehensive update list, you can follow
Hackage on Twitter, or the news feed.

Cheers,
Thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Andrew Coppin

Don Stewart wrote:

So, to stay up to date, but without drowning in data. Do one of:

* Pay attention to Haskell Cafe announcements
* Follow the Reddit Haskell news.
* Read the quarterly reports on Hackage
* Follow Planet Haskell
  


Interesting. Obviously I look at Haskell Cafe from time to time 
(although there's usually far too much traffic to follow it all). I 
wasn't aware of *any* of the other resources listed.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Conal Elliott
On Sat, Aug 14, 2010 at 10:11 PM, Bill Atkins watk...@alum.rpi.edu wrote:

 On Saturday Aug 14, 2010, at 12:50 AM, Conal Elliott wrote:

  And the IO monad is what Jerzy asked about.  I'm pointing out that the
 state monad does not capture concurrency, and the EDSL model does not
 capture FFI.  (Really, it depends which EDSL model.  I haven't seen one
 that can capture FFI.  And maybe not concurrency either.)
 

 So which model captures the way the IO monad works?


I don't think anyone has given a denotational (functional-style) model for
the meaning of IO.  As I wrote
elsewherehttp://conal.net/blog/posts/notions-of-purity-in-haskell/#comment-22829
:

IO carries the collective sins of our tribe, as the scapegoat did among the
ancient Hebrews. Or, as Simon Peyton Jones expressed it, “The IO monad has
become Haskell’s sin-bin. Whenever we don’t understand something, we toss it
in the IO monad.” (From Wearing the hair shirt – A retrospective on
Haskellhttp://research.microsoft.com/en-us/um/people/simonpj/papers/haskell-retrospective/.)
Is it likely that we can then come along later and give a compelling and
mathematically well-behaved notion of equality to our toxic waste pile? Or
will it insist on behaving anti-sociably, as our own home-grown Toxic
Avenger http://en.wikipedia.org/wiki/Toxic_Avenger?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Ivan Lazar Miljenovic
Vo Minh Thu not...@gmail.com writes:

 2010/8/15 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Don Stewart d...@galois.com writes:

     * Pay attention to Haskell Cafe announcements
     * Follow the Reddit Haskell news.
     * Read the quarterly reports on Hackage
     * Follow Planet Haskell

 And yet there are still many packages that fall under the radar with no
 announcements of any kind on initial release or even new versions :(

 If you're interested in a comprehensive update list, you can follow
 Hackage on Twitter, or the news feed.

Except that that doesn't tell you:

* The purpose of the library
* How a release differs from a previous one
* Why you should use it, etc.

Furthermore, several interesting discussions have arisen out of
announcement emails.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is bumping the version number evil, if it's not mandated by the PVP?

2010-08-15 Thread Sebastian Fischer

Hello,

On Aug 14, 2010, at 12:43 PM, Ross Paterson wrote:


When bumping only a.b.c.D, the new version is not installed as a
dependency if the old version already is installed (unless the new
version is explicitly demanded.) It seems bumping a.b.c.D has
advantages for some users and disadvantages for others.


How would bumping the major version change that?


Right, it doesn't. My worry with bumping only the patch level is that  
people who explicitly want to depend on the efficient version of my  
library need to depend on a.b.c.D and cannot follow the good practice  
of depending on a.b.*.


I actually like the idea of making a patch-level release *and* a new  
major release to get the best of both approaches. Do you think this is  
reasonable?


On Aug 14, 2010, at 10:49 PM, wren ng thornton wrote:

Asymptotic improvements may very well be worth a C or B bump [...]  
If your library is _defined_ by its performance characteristics,  
then a C or B bump would be appropriate since the complexity is  
effectively part of the API


To make things clear, I will shortly release a new version of the  
primes package for efficient generation of prime numbers. The new  
version asymptotically improves memory usage. The point of the library  
is to generate primes efficiently, so a major version bump feels  
justified. However, as explained above, I plan to additionally make a  
patch-level release.


Cheers,
Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Patai Gergely
 I don't agree.  A concurrent change is the effect of an IO action, not
 of the thread.  For example if a concurrent thread writes to an MVar,
 then that change becomes the effect of the next takeMVar, which gets
 executed.  If a concurrent thread changes a file on disk, then that
 changing becomes the effect of the next readFile, which reads the
 changed file.
But that's exactly what the model cannot handle. Look at the following
snippet again:

  let (x, world1) = getLine world0
  world2 = print (x+1) world1

This clearly says that the world returned by getLine and the world
consumed by print is the same one, since the state monad model is pure,
therefore world1 is immutable. However, this is not true, since someone
else could have modified it in the meantime. The state monad can only
describe a single thread, but that's a non-existent situation in the
case of I/O, since the world keeps changing outside the program even if
the program itself is single-threaded.

Gergely

-- 
http://www.fastmail.fm - IMAP accessible web-mail

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is bumping the version number evil, if it's not mandated by the PVP?

2010-08-15 Thread Ivan Lazar Miljenovic
Sebastian Fischer s...@informatik.uni-kiel.de writes:

 Hello,

 On Aug 14, 2010, at 12:43 PM, Ross Paterson wrote:

 When bumping only a.b.c.D, the new version is not installed as a
 dependency if the old version already is installed (unless the new
 version is explicitly demanded.) It seems bumping a.b.c.D has
 advantages for some users and disadvantages for others.

 How would bumping the major version change that?

 Right, it doesn't. My worry with bumping only the patch level is that
 people who explicitly want to depend on the efficient version of my
 library need to depend on a.b.c.D and cannot follow the good practice
 of depending on a.b.*.

Well, then you have = a.b.c.d   a.(b+1).  This is necessary for
whenever a bug-fix affecting your program was made in a dependency.

 I actually like the idea of making a patch-level release *and* a new
 major release to get the best of both approaches. Do you think this is
 reasonable?

It could work, as that way users packages that use your library whose
maintainers haven't updated the deps yet to use the new major version
can still get the benefits of the improved speed.

If you were to take this route, I would strongly advise stating in the
Description that the new major version is API-compatible with the old
one (with the major bump being for advertising reasons).

 To make things clear, I will shortly release a new version of the
 primes package for efficient generation of prime numbers. The new
 version asymptotically improves memory usage. The point of the library
 is to generate primes efficiently, so a major version bump feels
 justified. However, as explained above, I plan to additionally make a
 patch-level release.

Well, Brent Yorgey seems to the be the only person who uses primes in a
Hackage package [1], so maybe you can just do a major bump release and
co-ordinate with him to bump his np-extras package?

[1]:
http://bifunctor.homelinux.net/~roel/cgi-bin/hackage-scripts/revdeps/primes-0.1.1

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Vo Minh Thu
2010/8/15 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Vo Minh Thu not...@gmail.com writes:

 2010/8/15 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com:
 Don Stewart d...@galois.com writes:

     * Pay attention to Haskell Cafe announcements
     * Follow the Reddit Haskell news.
     * Read the quarterly reports on Hackage
     * Follow Planet Haskell

 And yet there are still many packages that fall under the radar with no
 announcements of any kind on initial release or even new versions :(

 If you're interested in a comprehensive update list, you can follow
 Hackage on Twitter, or the news feed.

 Except that that doesn't tell you:

 * The purpose of the library
 * How a release differs from a previous one
 * Why you should use it, etc.

 Furthermore, several interesting discussions have arisen out of
 announcement emails.

Sure, nor does it write a book chapter about some practical usage. I
mean (tongue in cheek) that the other ressource, nor even some proper
annoucement, provide all that.

I still remember the UHC annoucement (a (nearly) complete Haskell 98
compiler) thread where most of it was about lack of support for n+k
pattern.

But the bullet list above was to point Andrew a few places where he
could have learn about Text.

Cheers,
Thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Assorted AT fun and games

2010-08-15 Thread Andrew Coppin

It all began with

 class (Vector (Point x)) = HasSpace x where
   type Point x :: *

So far, so good.

I was rather surprised that you _can_ write

 class (Complete (Completed x)) = Incomplete x where
   type Completed x :: *
   complete :: x - Completed x

I was almost as surprised to discover that you _cannot_ write

 class (HasSpace x, Complete (Completed x), HasSpace (Completed x), 
Point x ~ Point (Completed x)) = Incomplete where...


It just means that every time you write an Incomplete instance, you 
might have to add the Point constraint manually. Which is mildly irritating.


More worrying, adding Point foo ~ Point bar to an instance declaration 
causes GHC to demand that you turn on Undecidable Instances, for reasons 
beyond my comprehension.


It's also interesting that when you write a class instance that has some 
constraint on it, and then you try to write a subclass instance, you 
still have to repeat the exact same constraint, even though the 
superclass instance declaration implies it. The only reason I can think 
of is that theoretically somebody could add a new superclass instance 
without the constraint. (Wouldn't that be an overlapping instance though?)


And now things get *really* interesting. Consider this:

 data Foo x = Foo !x !(Point x)

Surprisingly, GHC accepts this. This despite the rather obvious fact 
that Point x can exist if and only if x has a HasSpace instance. And 
yet, the type definition appears to say that x is simply an 
unconstrained type variable. Intriguing...


Next, you can't derive Eq or Show for this type, but you *can* declare 
them manually:


 instance (Show x, Show (Point x)) = Show (Foo x) where
   show (Foo x px) = Foo ( ++ show x ++ ) ( ++ show px ++ )

Again, no hint of the fact that this will only work if we have HasSpace 
x. And yet GHC happily accepts this.


I'm starting to think maybe I'm pushing the type system further than it 
can cope, and I should just completely redesign the whole thing...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help us test gio APIs!

2010-08-15 Thread Andy Stewart
Hi all,

I'm working on merge gio-branch
(https://patch-tag.com/r/AndyStewart/gio-branch/home) 
to gtk2hs-0.12.0.

GIO (http://library.gnome.org/devel/gio/stable/)
is cross-platform APIs for file operation, we can use gio APIs
develop file manager or similar application. 

If anyone want to use those APIs, help us test those APIs at
https://patch-tag.com/r/AndyStewart/gio-branch/home, 
then we can release gio-0.12.0 quicker. 

A GIO file-manager screenshot at : 
http://www.flickr.com/photos/48809...@n02/4793031888/

Thanks!

  -- Andy

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Assorted AT fun and games

2010-08-15 Thread Ivan Lazar Miljenovic
Andrew Coppin andrewcop...@btinternet.com writes:

 It all began with

  class (Vector (Point x)) = HasSpace x where
type Point x :: *

 So far, so good.

 I was rather surprised that you _can_ write

  class (Complete (Completed x)) = Incomplete x where
type Completed x :: *
complete :: x - Completed x

 I was almost as surprised to discover that you _cannot_ write

  class (HasSpace x, Complete (Completed x), HasSpace (Completed x),
 Point x ~ Point (Completed x)) = Incomplete where...

 It just means that every time you write an Incomplete instance, you
 might have to add the Point constraint manually. Which is mildly
 irritating.

Yeah... have to wait until at least 6.16 by all accounts :(

 More worrying, adding Point foo ~ Point bar to an instance declaration
 causes GHC to demand that you turn on Undecidable Instances, for
 reasons beyond my comprehension.

Because the type-checker isn't smart enough to figure this out itself.
And if you think yours is bad... (code taken from the new FGL):

,
| class (InductiveGraph (g n e)) = MappableGraph g n e where
| 
| gmap   :: (InductiveGraph (g n' e')) = (Context (g n e) - Context (g n' 
e'))
|   - g n e - g n' e'
| gmap f = fromContexts . map f . toContexts
| 
| nmap   :: ( InductiveGraph (g n' e)
|   , Node (g n e) ~ Node (g n' e)
|   , EdgeLabel (g n e) ~ EdgeLabel (g n' e))
|   = (NodeLabel (g n e) - NodeLabel (g n' e))
|  - g n e - g n' e
| nmap f = gmap f'
|   where
| f' (Context ei n l eo) = Context ei n (f l) eo
| 
| emap   :: ( InductiveGraph (g n e')
|   , Node (g n e) ~ Node (g n e')
|   , NodeLabel (g n e) ~ NodeLabel (g n e'))
|   = (EdgeLabel (g n e) - EdgeLabel (g n e'))
|  - g n e - g n e'
| emap f = gmap f'
| where
|   f' (Context ei n l eo) = Context (applyF ei) n l (applyF eo)
|   applyF = map (second f)
`

Since we can't apply constraints in the type-class, we have to apply
them in the methods :s

 It's also interesting that when you write a class instance that has
 some constraint on it, and then you try to write a subclass instance,
 you still have to repeat the exact same constraint, even though the
 superclass instance declaration implies it. The only reason I can
 think of is that theoretically somebody could add a new superclass
 instance without the constraint. (Wouldn't that be an overlapping
 instance though?)

What do you mean?  If it's what I think you mean, it's nothing specific
to type families:

,
| instance Eq a = Eq (Set a) where
|   t1 == t2  = (size t1 == size t2)  (toAscList t1 == toAscList t2)
| 
| instance Ord a = Ord (Set a) where
| compare s1 s2 = compare (toAscList s1) (toAscList s2) 
`

We have to specifically state that a is ordered even though Ord is a
sub-class of Eq...

 And now things get *really* interesting. Consider this:

  data Foo x = Foo !x !(Point x)

 Surprisingly, GHC accepts this. This despite the rather obvious fact
 that Point x can exist if and only if x has a HasSpace
 instance. And yet, the type definition appears to say that x is
 simply an unconstrained type variable. Intriguing...

Yeah, I'm not sure if I like or don't like this behaviour.  It's good
from the we shouldn't put class constraints in data types perspective,
but bad from the wtf does that even mean for non-instances?
perspective.

 Next, you can't derive Eq or Show for this type, but you *can* declare
 them manually:

  instance (Show x, Show (Point x)) = Show (Foo x) where
show (Foo x px) = Foo ( ++ show x ++ ) ( ++ show px ++ )

Yes, this slightly annoys me as well; Show is easy, Read is more
annoying.  I've resorted to specifying a non-TF version and then using
derive to work out what the instance should looks like and then tweaking
it myself.

 Again, no hint of the fact that this will only work if we have
 HasSpace x. And yet GHC happily accepts this.

I'm guessing it's implied somehow... but yeah :s

 I'm starting to think maybe I'm pushing the type system further than
 it can cope, and I should just completely redesign the whole thing...

Nah, push it as far as you can:

* We need people to push it and find weird things like this to see what
  is weird and what can be fixed.

* It will save you from converting it back down the track when type
  families take over the world... ;-)

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 03:01 , Bryan O'Sullivan wrote:
 On Sat, Aug 14, 2010 at 10:07 PM, Donn Cave d...@avvanta.com
 mailto:d...@avvanta.com wrote:
  We'll have a three way choice between programming
 elegance, correctness and efficiency.  If Haskell were more than
 just a research language, this might be its most prominent open
 sore, don't you think?
 
 No, that's just FUD. 

More to the point, there's nothing elegant about [Char] --- its sole
advantage is requiring no thought.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoBPgACgkQIn7hlCsL25WbWACgz+MXfwL6ly1Euv1X1HD7Gmg8
fO0Anj1LY6CqDyLjr0s5L2M5Okx8ie+/
=eIIs
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bill Atkins
No, not really.  Linked lists are very easy to deal with recursively and
Strings automatically work with any already-defined list functions.

On Sun, Aug 15, 2010 at 11:17 AM, Brandon S Allbery KF8NH 
allb...@ece.cmu.edu wrote:

 More to the point, there's nothing elegant about [Char] --- its sole
 advantage is requiring no thought.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Ertugrul Soeylemez
Patai Gergely patai_gerg...@fastmail.fm wrote:

  I don't agree.  A concurrent change is the effect of an IO action,
  not of the thread.  For example if a concurrent thread writes to an
  MVar, then that change becomes the effect of the next takeMVar,
  which gets executed.  If a concurrent thread changes a file on disk,
  then that changing becomes the effect of the next readFile, which
  reads the changed file.

 But that's exactly what the model cannot handle. Look at the following
 snippet again:

   let (x, world1) = getLine world0
   world2 = print (x+1) world1

 This clearly says that the world returned by getLine and the world
 consumed by print is the same one, since the state monad model is
 pure, therefore world1 is immutable. However, this is not true, since
 someone else could have modified it in the meantime. The state monad
 can only describe a single thread, but that's a non-existent situation
 in the case of I/O, since the world keeps changing outside the program
 even if the program itself is single-threaded.

No.  As you say the world1 value is immutable, but that's not
contradictory.  If between 'getLine' and 'print' something was done by a
concurrent thread, then that change to the world is captured by 'print'.

See for example the following code:

  var - newEmptyMVar
  forkIO $ threadDelay 100  putMVar var 15
  takeMVar var = print

Let's translate it:

  \world0 -
  let (var, world1) = newEmptyMVar world0
  world2 = (forkIO $ threadDelay 100  putMVar var 15) world1
  (result, world3) = takeMVar var world2
  in print result world3

The subthread has the following code:

  \world0 -
  let world1 = threadDelay 100 world0
  in putMVar var 15 world1

In the main thread the delay of one second and the change to the MVar is
/not/ an effect of another thread.  There is no notion of threads at
all.  It's a side effect of takeMVar.  The thread launched by forkIO
becomes part of the opaque world variable, which captures everything.
Otherwise we would have to say that the state monad model doesn't
capture user input either, because conceptually there is no difference
between a user typing something and a concurrent thread writing to
stdin.

IO has no specific notion for threads.  Threads are just side effects.
Things caused by threads is captured by normal IO actions like getLine
and takeMVar.  That's not a flaw of the interpretation as a state monad.
That's a flaw of the IO monad itself.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Tillmann Rendel

Ertugrul Soeylemez wrote:

 let (x, world1) = getLine world0
 world2 = print (x+1) world1


If between 'getLine' and 'print' something was done by a
concurrent thread, then that change to the world is captured by 'print'.


But in a world passing interpretation of IO, print is supposed to be a 
pure Haskell function. So the value world2 can only depend on the values 
of print and world1, but not on the actions of some concurrent thread.


If print is not restricted to be a pure Haskell function, we don't need 
the world passing in the first place.


  Tillmann
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Donn Cave
Quoth Bryan O'Sullivan b...@serpentine.com,
 On Sat, Aug 14, 2010 at 10:07 PM, Donn Cave d...@avvanta.com wrote:
...
 ByteString will continue to be the obvious choice
 for big data loads.

 Don't confuse I have big data with I need bytes. If you are working with
 bytes, use bytestring. If you are working with text, outside of a few narrow
 domains you should use text.

I wonder how many ByteString users are `working with bytes', in the
sense you apparently mean where the bytes are not text characters.
My impression is that in practice, there is a sizeable contingent
out here using ByteString.Char8 and relatively few applications for
the Word8 type.  Some of it should no doubt move to Text, but the
ability to work with native packed data - minimal processing and
space requirements, interoperability with foreign code, mmap, etc. -
is attractive enough that the choice can be less than obvious.

Donn Cave, d...@avvanta.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Donn Cave
Quoth Bill Atkins watk...@alum.rpi.edu,

 No, not really.  Linked lists are very easy to deal with recursively and
 Strings automatically work with any already-defined list functions.

Yes, they're great - a terrible mistake, for a practical programming
language, but if you fail to recognize the attraction, you miss some of
the historical lesson on emphasizing elegance and correctness over
practical performance.

Donn Cave, d...@avvanta.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Felipe Lessa
On Sun, Aug 15, 2010 at 12:50 PM, Donn Cave d...@avvanta.com wrote:
 I wonder how many ByteString users are `working with bytes', in the
 sense you apparently mean where the bytes are not text characters.
 My impression is that in practice, there is a sizeable contingent
 out here using ByteString.Char8 and relatively few applications for
 the Word8 type.  Some of it should no doubt move to Text, but the
 ability to work with native packed data - minimal processing and
 space requirements, interoperability with foreign code, mmap, etc. -
 is attractive enough that the choice can be less than obvious.

Using ByteString.Char8 doesn't mean your data isn't a stream of bytes,
it means that it is a stream of bytes but for convenience you prefer
using Char8 functions.  For example, a DNA sequence (AATCGATACATG...)
is a stream of bytes, but it is better to write 'A' than 65.

But yes, many users of ByteStrings should be using Text. =)

Cheers!

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Bulat Ziganshin
Hello Tillmann,

Sunday, August 15, 2010, 7:40:54 PM, you wrote:

 But in a world passing interpretation of IO, print is supposed to be a
 pure Haskell function. So the value world2 can only depend on the values
 of print and world1, but not on the actions of some concurrent thread.

the whole World includes any concurrent thread though ;)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Assorted AT fun and games

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 09:00 , Andrew Coppin wrote:
  class (Vector (Point x)) = HasSpace x where
type Point x :: *
(...)
 And now things get *really* interesting. Consider this:
 
  data Foo x = Foo !x !(Point x)
 
 Surprisingly, GHC accepts this. This despite the rather obvious fact that
 Point x can exist if and only if x has a HasSpace instance. And yet, the
 type definition appears to say that x is simply an unconstrained type
 variable. Intriguing...

Maybe I'm missing something in all the type machinery I elided, but it looks
to me like you have that backwards:  HasSpace x requires Point x but not
vice versa.  Your actual usage may require the reverse association, but the
definition of Foo won't be modified by that usage --- only applications of
that definition.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoFikACgkQIn7hlCsL25VIJgCbB/3zqsATPssYNFsCD/H5fMOO
DnUAn2+gBqlHyD0FyGFANSyVxWdI0PQR
=/SmY
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 11:25 , Bill Atkins wrote:
 No, not really.  Linked lists are very easy to deal with recursively and
 Strings automatically work with any already-defined list functions.
 
 On Sun, Aug 15, 2010 at 11:17 AM, Brandon S Allbery KF8NH
 allb...@ece.cmu.edu mailto:allb...@ece.cmu.edu wrote:
 
 More to the point, there's nothing elegant about [Char] --- its sole
 advantage is requiring no thought.

Except that it seems to me that a number of functions in Data.List are
really functions on Strings and not especially useful on generic lists.
There is overlap but it's not as large as might be thought.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoFt4ACgkQIn7hlCsL25V+OACfXngN6ZX5L7AL153AkRYDFnqZ
jqsAnA3Lem5LioDVS5bc0ADGzHwWsKFE
=ehkx
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Tillmann Rendel

Bulat Ziganshin wrote:

But in a world passing interpretation of IO, print is supposed to be a
pure Haskell function. So the value world2 can only depend on the values
of print and world1, but not on the actions of some concurrent thread.


the whole World includes any concurrent thread though ;)


Oh I see. So given world1, print can simulate the behavior of the 
concurrent thread to take it into account when constructing world2. 
Since that simulation depends only on world1, print is still pure.


Does that mean that world passing *does* account for concurrency after all?

  Tillmann
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 11:40 , Tillmann Rendel wrote:
 But in a world passing interpretation of IO, print is supposed to be a pure
 Haskell function. So the value world2 can only depend on the values of print
 and world1, but not on the actions of some concurrent thread.
 
 If print is not restricted to be a pure Haskell function, we don't need the
 world passing in the first place.

I am confused by this discussion.  I originally thought some time back that
IO was about world passing, but in fact it's just handing off a baton to
insure that a particular sequence of IO functions is executed in the
specified sequence and not reordered.  Nothing in the baton is intended to
represent the actual state of the world, nor is anything said about
concurrent actions either in another thread of the current program or
elsewhere outside the program; only ordering of calls in the *current*
thread of execution.  (Which, hmm, implies that unsafePerformIO and
unsafeInterleaveIO are conceptually similar to forkIO.)

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoGpUACgkQIn7hlCsL25U5SwCglJdUpOKbrFLmDO2X22nDq/no
UTIAoMllTt9LXOlblVaocbtVnRIx4dMY
=hCIW
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Assorted AT fun and games

2010-08-15 Thread Andrew Coppin

Brandon S Allbery KF8NH wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 09:00 , Andrew Coppin wrote:
  

 class (Vector (Point x)) = HasSpace x where
   type Point x :: *


(...)
  

And now things get *really* interesting. Consider this:

 data Foo x = Foo !x !(Point x)

Surprisingly, GHC accepts this. This despite the rather obvious fact that
Point x can exist if and only if x has a HasSpace instance. And yet, the
type definition appears to say that x is simply an unconstrained type
variable. Intriguing...



Maybe I'm missing something in all the type machinery I elided, but it looks
to me like you have that backwards:  HasSpace x requires Point x but not
vice versa.  Your actual usage may require the reverse association, but the
definition of Foo won't be modified by that usage --- only applications of
that definition.
  


Well, since Point is part of the definition of HasSpace, and therefore 
Point x is defined only if an instance HasSpace x exists. I'm not sure 
how that's Point x doesn't require HasSpace x.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Andrew Coppin

Donn Cave wrote:

I wonder how many ByteString users are `working with bytes', in the
sense you apparently mean where the bytes are not text characters.
My impression is that in practice, there is a sizeable contingent
out here using ByteString.Char8 and relatively few applications for
the Word8 type.  Some of it should no doubt move to Text, but the
ability to work with native packed data - minimal processing and
space requirements, interoperability with foreign code, mmap, etc. -
is attractive enough that the choice can be less than obvious.
  


I use ByteString for various binary-processing stuff. I also use it for 
string-processing, but that's mainly because I didn't know anything else 
existed. I'm sure lots of other people are using stuff like Data.Binary 
to serialise raw binary data using ByteString too.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Tillmann Rendel

Brandon S Allbery KF8NH wrote:

I am confused by this discussion.  I originally thought some time back that
IO was about world passing, but in fact it's just handing off a baton to
insure that a particular sequence of IO functions is executed in the
specified sequence and not reordered.  Nothing in the baton is intended to
represent the actual state of the world, nor is anything said about
concurrent actions either in another thread of the current program or
elsewhere outside the program; only ordering of calls in the *current*
thread of execution.


That explains how the IO monad forces side-effecting functions into a 
specified sequence, but this discussion is about how to understand what 
these side-effecting functions do in a *pure* framework. So the idea is 
to regard, for example, putStr as a pure function from a world state to 
a different world state, assuming that the world state contains a String 
which represents the contents of the terminal. We could then implement 
and understand putStr in pure Haskell:


  data World = World {
terminal :: String
...
  }

  type IO a = World - (World, a)

  putStr :: String - World - (World, ())
  putStr str world = (world {terminal = terminal world ++ str}, ())

The benefit of this point of view is that we can analyze the behavior of 
putStr. For example, by equational reasoning, we could derive the 
following equation:


  putStr s1  putStr s2   ==   putStr (s1 ++ s2)

It seems that we can account for more features of IO by adding more 
fields to the World record. This discussion is about whether we can 
account for *all* of IO this way.


  Tillmann
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Andrew Coppin

Donn Cave wrote:

Quoth Bill Atkins watk...@alum.rpi.edu,

  

No, not really.  Linked lists are very easy to deal with recursively and
Strings automatically work with any already-defined list functions.



Yes, they're great - a terrible mistake, for a practical programming
language, but if you fail to recognize the attraction, you miss some of
the historical lesson on emphasizing elegance and correctness over
practical performance.
  


And if you fail to recognise what a grave mistake placing performance 
before correctness is, you end up with things like buffer overflow 
exploits, SQL injection attacks, the Y2K bug, programs that can't handle 
files larger than 2GB or that don't understand Unicode, and so forth. 
All things that could have been almost trivially avoided if everybody 
wasn't so hung up on absolute performance at any cost.


Sure, performance is a priority. But it should never be the top 
priority. ;-)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 13:53 , Andrew Coppin wrote:
 injection attacks, the Y2K bug, programs that can't handle files larger than
 2GB or that don't understand Unicode, and so forth. All things that could
 have been almost trivially avoided if everybody wasn't so hung up on
 absolute performance at any cost.

Now that's a bit unfair; nobody imagined back when lseek() was enshrined in
the Unix API that it would still be in use when a (long) wasn't big enough
:)  (Remember that Unix is itself a practical example of a research platform
avoiding success at any cost gone horribly wrong.)

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoK2gACgkQIn7hlCsL25VaHgCcCj8T8Qqfx4Co1lXZCH7BApkW
iI8AoNcSabjLso9nXBfujeI+diC8rM78
=FwBb
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bryan O'Sullivan
On Sat, Aug 14, 2010 at 6:05 PM, Bryan O'Sullivan b...@serpentine.comwrote:


- If it's not good enough, and the fault lies in a library you chose,
report a bug and provide a test case.

 As a case in point, I took the string search benchmark that Daniel shared
on Friday, and boiled it down to a simple test case: how long does it take
to read a 31MB file?

GNU wc -m:

   - en_US.UTF-8: 0.701s

text 0.7.1.0:

   - lazy text: 1.959s
   - strict text: 3.527s

darcs HEAD:

   - lazy text: 0.749s
   - strict text: 0.927s
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 13:27 , Tillmann Rendel wrote:
 Brandon S Allbery KF8NH wrote:
 I am confused by this discussion.  I originally thought some time back that
 IO was about world passing, but in fact it's just handing off a baton to
 insure that a particular sequence of IO functions is executed in the
 specified sequence and not reordered.  Nothing in the baton is intended to
 represent the actual state of the world, nor is anything said about
 concurrent actions either in another thread of the current program or
 elsewhere outside the program; only ordering of calls in the *current*
 thread of execution.
 
 That explains how the IO monad forces side-effecting functions into a
 specified sequence, but this discussion is about how to understand what
 these side-effecting functions do in a *pure* framework. So the idea is to

I think that *is* included in what I said, by negation:  it doesn't. Period.
 (As Conal observed.)  Trying to take the Haskell representation of IO as
the basis for a formal description of I/O actions is pretty much doomed from
the start; adding records or etc. will at best mask the symptoms.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoLP8ACgkQIn7hlCsL25W4QACgtJ4bz/W5fHVV/DxNgt8R39C8
ZkEAnj7rUnoUh4UQDFRdLeHKVmP8HLKS
=jnty
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Andrew Coppin

Brandon S Allbery KF8NH wrote:

(Remember that Unix is itself a practical example of a research platform
avoiding success at any cost gone horribly wrong.)
  


I haven't used Erlang myself, but I've heard it described in a similar 
way. (I don't know how true that actually is...)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Daniel Fischer
On Sunday 15 August 2010 20:04:01, Bryan O'Sullivan wrote:
 On Sat, Aug 14, 2010 at 6:05 PM, Bryan O'Sullivan 
b...@serpentine.comwrote:
 - If it's not good enough, and the fault lies in a library you
  chose, report a bug and provide a test case.
 
 As a case in point, I took the string search benchmark that Daniel shared
 on Friday, and boiled it down to a simple test case: how long does it
 take to read a 31MB file?

 GNU wc -m:

- en_US.UTF-8: 0.701s

 text 0.7.1.0:

- lazy text: 1.959s
- strict text: 3.527s

 darcs HEAD:

- lazy text: 0.749s
- strict text: 0.927s

That's great. If that performance difference is a show stopper, one 
shouldn't go higher-level than C anyway :)
(doesn't mean one should stop thinking about further speed-up, though)

Out of curiosity, what kind of speed-up did your Friday fix bring to the 
searching/replacing functions?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 8/15/10 14:34 , Andrew Coppin wrote:
 Brandon S Allbery KF8NH wrote:
 (Remember that Unix is itself a practical example of a research platform
 avoiding success at any cost gone horribly wrong.)
 
 I haven't used Erlang myself, but I've heard it described in a similar way.
 (I don't know how true that actually is...)

Similar case, actually:  internal research project with internal practical
uses, then got discovered and productized by a different internal group.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxoNoAACgkQIn7hlCsL25XSAgCgtLKTtT8YN99KsArnhW2kMDvh
oHcAnR1QrfIaq3hmzqU7yF31NZubEMsR
=zpv1
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bryan O'Sullivan
On Sun, Aug 15, 2010 at 11:39 AM, Daniel Fischer
daniel.is.fisc...@web.dewrote:

 Out of curiosity, what kind of speed-up did your Friday fix bring to the
 searching/replacing functions?


Quite a bit!

text 0.7.1.0 and 0.7.2.1:

   - 1.056s

darcs HEAD:

   - 0.158s
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Patai Gergely
 No.  As you say the world1 value is immutable, but that's not
 contradictory.  If between 'getLine' and 'print' something was done by a
 concurrent thread, then that change to the world is captured by 'print'.
Well, that's technically true, but it basically amounts to saying that
the 'model' of IO is itself. If I see 'print x', I don't really think of
an action that performs arbitrary side effects and prints x in the
process (unless some error prevents even that). Some notion of
compositionality is required, which would allow me to state how 'print
x' contributes to the changes of the world in a way that doesn't depend
on any context. Actions in the state monad are composable in that sense,
while the same doesn't apply to the IO monad when explained in terms of
state passing.

Gergely

-- 
http://www.fastmail.fm - The professional email service

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Donn Cave
Quoth Andrew Coppin andrewcop...@btinternet.com,
...
 And if you fail to recognise what a grave mistake placing performance 
 before correctness is, you end up with things like buffer overflow 
 exploits, SQL injection attacks, the Y2K bug, programs that can't handle 
 files larger than 2GB or that don't understand Unicode, and so forth. 
 All things that could have been almost trivially avoided if everybody 
 wasn't so hung up on absolute performance at any cost.

 Sure, performance is a priority. But it should never be the top 
 priority. ;-)

You should never have to choose.  Not to belabor the point, but to
dismiss all that as the work of morons who weren't as wise as we are,
is the same mistake from the other side of the wall - performance counts.
If you solve the problem by assigning a priority to one or the other,
you aren't solving the problem.

Donn Cave, d...@avvanta.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Daniel Fischer
On Sunday 15 August 2010 20:53:32, Bryan O'Sullivan wrote:
 On Sun, Aug 15, 2010 at 11:39 AM, Daniel Fischer

 daniel.is.fisc...@web.dewrote:
  Out of curiosity, what kind of speed-up did your Friday fix bring to
  the searching/replacing functions?

 Quite a bit!

 text 0.7.1.0 and 0.7.2.1:

- 1.056s

 darcs HEAD:

- 0.158s

Awesome :D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Ertugrul Soeylemez
Tillmann Rendel ren...@mathematik.uni-marburg.de wrote:

 Bulat Ziganshin wrote:
  But in a world passing interpretation of IO, print is supposed to
  be a pure Haskell function. So the value world2 can only depend on
  the values of print and world1, but not on the actions of some
  concurrent thread.
 
  the whole World includes any concurrent thread though ;)

 Oh I see. So given world1, print can simulate the behavior of the
 concurrent thread to take it into account when constructing world2.
 Since that simulation depends only on world1, print is still pure.

 Does that mean that world passing *does* account for concurrency after
 all?

Exactly.  If at any point you use forkIO, then the world is updated to
include the new thread.

That's why I find it wrong to say that this mental model doesn't capture
concurrency.  It just has no explicit notion for it, but neither has IO.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Gregory Collins
Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes:

 Don Stewart d...@galois.com writes:

 * Pay attention to Haskell Cafe announcements
 * Follow the Reddit Haskell news.
 * Read the quarterly reports on Hackage
 * Follow Planet Haskell

 And yet there are still many packages that fall under the radar with no
 announcements of any kind on initial release or even new versions :(

Subscribe to http://hackage.haskell.org/packages/archive/recent.rss in
your RSS reader: problem solved!

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Ertugrul Soeylemez
Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

 On 8/15/10 11:40 , Tillmann Rendel wrote:
  But in a world passing interpretation of IO, print is supposed to be
  a pure Haskell function. So the value world2 can only depend on the
  values of print and world1, but not on the actions of some
  concurrent thread.
 
  If print is not restricted to be a pure Haskell function, we don't
  need the world passing in the first place.

 I am confused by this discussion.  I originally thought some time back
 that IO was about world passing, but in fact it's just handing off a
 baton to insure that a particular sequence of IO functions is executed
 in the specified sequence and not reordered.  Nothing in the baton
 is intended to represent the actual state of the world, nor is
 anything said about concurrent actions either in another thread of the
 current program or elsewhere outside the program; only ordering of
 calls in the *current* thread of execution.  (Which, hmm, implies that
 unsafePerformIO and unsafeInterleaveIO are conceptually similar to
 forkIO.)

IO is just a simple language to express impure operations.  What we
discuss is how to /interpret/ IO, or more specifically how to translate
IO computations into pure ones mentally.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] bug in Network.Browser

2010-08-15 Thread Alexander Kotelnikov
Hello.

Yesterday I hit a bug in Network.Browser: connection in the connection
pool is not reused if you are connecting to a destination with
qualified port (not 80 for HTTP or 80 but explicitly provided like
http://www.google.com:80). The reason for the failure is quite trivial,
but I had not found an easy fix which won't break anything.


Problem is that in TCP.hs function

isTCPConnectedTo :: HandleStream ty - String - IO Bool
isTCPConnectedTo conn name = do
   v - readMVar (getRef conn)
   case v of
 ConnClosed - return False
 _
  | map toLower (connHost v) == map toLower name -
  catch (getPeerName (connSock v)  return True) (const $ return False)
  | otherwise - return False

socket's hostname, (connHost v) is compared to hostname or hostname:port
which is stored in name.

Hope this message will reach this code maintainers

Alexander

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is bumping the version number evil, if it's not mandated by the PVP?

2010-08-15 Thread Sebastian Fischer

My worry with bumping only the patch level is that
people who explicitly want to depend on the efficient version of my
library need to depend on a.b.c.D and cannot follow the good practice
of depending on a.b.*.


Well, then you have = a.b.c.d   a.(b+1).


Ok, it seems this is less of an issue than I initially thought. I have  
changed my mind and will probably make a patch-level release without  
an identical major release. (I'll make an additional major release  
with a generalised API however.)


Thanks!
Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] xemacs newbie question - haskell mode

2010-08-15 Thread rgowka1
HI -

I have been struggling to get the Xemacs recognize hs file. I have installed
the Haskell-mode.. However I keep getting the message File mode
specification error: (wrong-number-of-arguments require 3).. How do I go
about fixing this??

Many thanks
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Ertugrul Soeylemez
Patai Gergely patai_gerg...@fastmail.fm wrote:

  No.  As you say the world1 value is immutable, but that's not
  contradictory.  If between 'getLine' and 'print' something was done
  by a concurrent thread, then that change to the world is captured by
  'print'.

 Well, that's technically true, but it basically amounts to saying that
 the 'model' of IO is itself. If I see 'print x', I don't really think
 of an action that performs arbitrary side effects and prints x in the
 process (unless some error prevents even that). Some notion of
 compositionality is required, which would allow me to state how 'print
 x' contributes to the changes of the world in a way that doesn't
 depend on any context. Actions in the state monad are composable in
 that sense, while the same doesn't apply to the IO monad when
 explained in terms of state passing.

Why not?

I don't see any problems here.  Note that the mental model of IO I
presented is not explicit state passing, but a state /monad/.  I'm
proposing the hypothetical existence of a function like this:

  advanceEverything :: Universe - Universe

such that:

  print x =
\world0 -
doTheActualPrinting x (advanceEverything world0)

After all 'print' is not constrained to the effect of printing
something.  All sorts of things can happen while printing, including
even network communication, when stdout is not a terminal.  In IO
everything can happen everywhere.

The advanceEverything function could just as well be used by (=)
instead of the individual IO computations.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] couchdb - newView command

2010-08-15 Thread Andrew U. Frank
  i use haskell couchdb 0.10 with more luck than others: it works for me
  quite well. I have been careful to convert to json strings separately
  from the calls to runCouchDB - so i could check that the values were
  correct.

i sense there is a difficulty with 'newView' - it does not allow
to
update a viewset, but one has to select for each change a new
viewset
(design) name; which is sort of annoying. 

the newView operation should ptobably be called 'newViewset',
because it
sets multiple views in one design document. it would be nice, if
that
could not only be set, but also updated. (the full set at once)

i would also recommend that the first parameter is of type DB
and not
String - or are there any particular reasons for this?

i appreciate the package and i like it! 

andrew
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Bill Atkins
On Sunday, August 15, 2010, Tillmann Rendel
ren...@mathematik.uni-marburg.de wrote:
 Bulat Ziganshin wrote:

 But in a world passing interpretation of IO, print is supposed to be a
 pure Haskell function. So the value world2 can only depend on the values
 of print and world1, but not on the actions of some concurrent thread.


 the whole World includes any concurrent thread though ;)


 Oh I see. So given world1, print can simulate the behavior of the concurrent 
 thread to take it into account when constructing world2. Since that 
 simulation depends only on world1, print is still pure.

 Does that mean that world passing *does* account for concurrency after all?

   Tillmann
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


I guess I don't see how forkIO, MVar's etc are more problematic than
any other kind of I/O.  Consider:

  line - hGetLine myHandle
  putStrLn line

The world could very easily change between these two statements -
someone could delete the file we're reading from or change its
contents or truncate it.

In fact, the RealWorld will always be in flux and will never, ever
be the same from one call to the next (even consider things like the
wall clock, which will tick in between the time you generated world0
and the time you pass world0 to a new IO action).

I don't think threads are the only problem with the State RealWorld
a interpretation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: darcs 2.5 beta 3

2010-08-15 Thread Reinier Lamers
Hi all,

The darcs team would like to announce the immediate availability of darcs 2.5
beta 3 (also known as darcs 2.4.98.3 due to Cabal restrictions). Important 
changes since darcs 2.4.4 are:

   * trackdown can now do binary search with the --bisect option
   * darcs always stores patch metadata encoded with UTF-8
   * diff now supports the --index option
   * amend-record now supports the --ask-deps option
   * apply now supports the --match option
   * amend-record has a new --keep-date option
   * inventory-changing commands (like record and pull) now operate in
 constant time with respect to the number of patches in the repository
   * the push, pull, send and fetch commands no longer set the default
 repository by default
   * the --edit-description option is now on by default for the send command

You may notice that a line obliterate has a -o flag to save obliterated 
patch was removed from this list of changes since the darcs 2.5 beta 2 
announcement. We have postponed this feature because we discovered some 
problems with it, and we want to take the time to fix them adequately. On the 
other hand, a line diff now supports the --index option was added since the 
last beta :)

If you have installed the Haskell Platform or cabal-install, you can install
this beta release by doing:

  $ cabal update
  $ cabal install darcs-beta

Alternatively, you can download the tarball from 
http://darcs.net/releases/darcs-2.4.98.3.tar.gz and build it by hand as 
explained in the README file. (You may notice that the Unix permissions in 
this tarball are weird - all files are 0600. That is because of Cabal bug 
#627: http://hackage.haskell.org/trac/hackage/ticket/627. It will be fixed in 
the final release.)

Kind Regards,
the darcs release manager,
Reinier Lamers  


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


[Haskell-cafe] hgettext and cabal

2010-08-15 Thread abau
Hi,

[1] describes how to use hgettext with cabal. When running runhaskell
Setup build this works fine. But cabal build says:
Not in scope: `__MESSAGE_CATALOG_DOMAIN__'
Not in scope: `__MESSAGE_CATALOG_DIR__'

[1] says: __MESSAGE_CATALOG_DOMAIN__ and __MESSAGE_CATALOG_DIR__ are macro
definitions, whose hold configured strings from the Cabal.

Why cabal build does not expand these macros?

Thank you.


[1]
http://www.haskell.org/haskellwiki/Internationalization_of_Haskell_programs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] couchdb - newView command

2010-08-15 Thread Antoine Latter
CCing the maintainer of the CouchDB package.

On Sun, Aug 15, 2010 at 3:34 PM, Andrew U. Frank
fran...@geoinfo.tuwien.ac.at wrote:
  i use haskell couchdb 0.10 with more luck than others: it works for me
  quite well. I have been careful to convert to json strings separately
  from the calls to runCouchDB - so i could check that the values were
  correct.

        i sense there is a difficulty with 'newView' - it does not allow
        to
        update a viewset, but one has to select for each change a new
        viewset
        (design) name; which is sort of annoying.

        the newView operation should ptobably be called 'newViewset',
        because it
        sets multiple views in one design document. it would be nice, if
        that
        could not only be set, but also updated. (the full set at once)

        i would also recommend that the first parameter is of type DB
        and not
        String - or are there any particular reasons for this?

        i appreciate the package and i like it!

        andrew


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread wren ng thornton

Bryan O'Sullivan wrote:

As a case in point, I took the string search benchmark that Daniel shared
on Friday, and boiled it down to a simple test case: how long does it take
to read a 31MB file?

GNU wc -m:

   - en_US.UTF-8: 0.701s

text 0.7.1.0:

   - lazy text: 1.959s
   - strict text: 3.527s

darcs HEAD:

   - lazy text: 0.749s
   - strict text: 0.927s


When should we expect to see the HEAD stamped and numbered? After some 
of the recent benchmark dueling re web frameworks, I know Text got a bad 
rap compared to ByteString. It'd be good to stop the FUD early. 
Repeating the above in the announcement should help a lot.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Don Stewart
wren:
 Bryan O'Sullivan wrote:
 As a case in point, I took the string search benchmark that Daniel shared
 on Friday, and boiled it down to a simple test case: how long does it take
 to read a 31MB file?

 GNU wc -m:

- en_US.UTF-8: 0.701s

 text 0.7.1.0:

- lazy text: 1.959s
- strict text: 3.527s

 darcs HEAD:

- lazy text: 0.749s
- strict text: 0.927s

 When should we expect to see the HEAD stamped and numbered? After some  
 of the recent benchmark dueling re web frameworks, I know Text got a bad  
 rap compared to ByteString. It'd be good to stop the FUD early.  
 Repeating the above in the announcement should help a lot.

For what its worth, for several bytestring announcements I published
comprehensive function-by-function comparisions of performance on
enormous data sets, until there was unambiguous evidence bytestring was
faster than List.

E.g http://www.mail-archive.com/hask...@haskell.org/msg18596.html

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Assorted AT fun and games

2010-08-15 Thread wren ng thornton

Brandon S Allbery KF8NH wrote:

On 8/15/10 09:00 , Andrew Coppin wrote:

 class (Vector (Point x)) = HasSpace x where
   type Point x :: *

(...)

And now things get *really* interesting. Consider this:

 data Foo x = Foo !x !(Point x)

Surprisingly, GHC accepts this. This despite the rather obvious fact that
Point x can exist if and only if x has a HasSpace instance. And yet, the
type definition appears to say that x is simply an unconstrained type
variable. Intriguing...


Maybe I'm missing something in all the type machinery I elided, but it looks
to me like you have that backwards:  HasSpace x requires Point x but not
vice versa.  Your actual usage may require the reverse association, but the
definition of Foo won't be modified by that usage --- only applications of
that definition.



Not quite. What we're doing is defining a type function: Point. We may 
ask, then, what is the kind of Point? I don't know what the notation is 
for writing it in GHC these days, but the kind is:


Point :: (x::*) - HasSpace x - *

That is, we accept a type as an argument. Let's call that argument x. 
Then we accept a proof of HasSpace for x. This argument will be computed 
by searching for typeclass instances, where the instance itself is the 
proof. Given these two arguments, Point can return a type (namely by 
projecting it from the instance record). This is the same for any other 
method of a typeclass; we don't write the class constraint in the 
function types either, because it's implied by being in a typeclass 
definition. Ditto for the types of record selectors.


Translating this kind down to its type-level ramifications is where 
things get weird, because of how instances are implicitly discovered and 
passed around. Effectively, instances have their own function space 
distinct from (-).


In any case, it seems that the only sensible way to get a result back 
from Point is if we provide it with both a source type and a class 
instance for that type. Thus, when asking what the kind of Foo is (or 
the type of the other Foo for that matter) there should be a constraint. 
How else can we pass the correct instance to Point?


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread wren ng thornton

Brandon S Allbery KF8NH wrote:

only ordering of calls in the *current*
thread of execution.  (Which, hmm, implies that unsafePerformIO and
unsafeInterleaveIO are conceptually similar to forkIO.)


Implementationally they are very similar (at least as far as the baton 
is concerned). How hard we should press that for getting semantics out 
of them ...well, that's a different question :)


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Brandon S Allbery KF8NH

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 08/15/2010 08:32 PM, wren ng thornton wrote:
 Brandon S Allbery KF8NH wrote:
 only ordering of calls in the *current*
 thread of execution.  (Which, hmm, implies that unsafePerformIO and
 unsafeInterleaveIO are conceptually similar to forkIO.)

 Implementationally they are very similar (at least as far as the
 baton is concerned). How hard we should press that for getting
 semantics out of them ...well, that's a different question :)

I would say the discussion to this point is at worst neutral and at
best mildly supports doing so.
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.10 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxojO0ACgkQIn7hlCsL25XHmwCglxNzX6CvccQs42lXXrNmWA37
LG0An3+vlcvhdcXd5XmNnuO0Vw/Uu2A1
=on2m
-END PGP SIGNATURE-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Ivan Lazar Miljenovic
Gregory Collins g...@gregorycollins.net writes:

 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes:

 Don Stewart d...@galois.com writes:

 * Pay attention to Haskell Cafe announcements
 * Follow the Reddit Haskell news.
 * Read the quarterly reports on Hackage
 * Follow Planet Haskell

 And yet there are still many packages that fall under the radar with no
 announcements of any kind on initial release or even new versions :(

 Subscribe to http://hackage.haskell.org/packages/archive/recent.rss in
 your RSS reader: problem solved!

As I said in reply to someone else: that won't help you get the intent
of a library, how it has changed from previous versions, etc.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Deprecated gtk2hs functions

2010-08-15 Thread Andrew U. Frank

may i suggest that the description of the package, where it lists the
depreciated functions, give also a hint, how the function should be
replaced. i often hit the wall of depreciated functions when i try to
use a packaged not having been compiled for a while and i have to
replace the functions. then the searching starts... - if the information
were included in the package description (automatically produced with
haddock from a bit of text in the source code, written by somebody that
did the change and has the information at his fingertips), it would save
a lot of searching and failing upgrade experiences. gtk2hs is just a
point in case, but it applies generally.

any comments?

andrew


On Fri, 2010-07-16 at 17:44 -0400, Alex Rozenshteyn wrote:
 More like buttonActivated [1].
 
 
 Has it been decided that button-specific events are going to be
 deprecated in favor of their general widget equivalents, with
 buttonActivated being an (IMO) awkward title for buttonClicked?
 
 
 [1] 
 http://www.haskell.org/gtk2hs/docs/current/Graphics-UI-Gtk-Buttons-Button.html#v%3AbuttonActivated
 
 On Fri, Jul 16, 2010 at 3:20 PM, Thomas DuBuisson
 thomas.dubuis...@gmail.com wrote:
 You mean something like buttonPressEvent [1]?
 
  on button buttonPressEvent
 
 You can define signals, the constructor is exposed.
 
 
 
 [1]
 
 http://www.haskell.org/gtk2hs/docs/current/Graphics-UI-Gtk-Abstract-Widget.html#v%3AexposeEvent
 
 
 
 On Fri, Jul 16, 2010 at 11:36 AM, Alex Rozenshteyn
 rpglove...@gmail.com wrote:
  I recently started playing around with gtk2hs.
  I noticed that `onClicked`, `afterClicked`, etc. functions
 have been
  deprecated, presumably in favor of the `on` and `after`
 functions in the
  Glib signals module, but I couldn't find a collection of the
 appropriate
  signals to replace the functionality.
 
  Am I simply being blind?
 
  --
Alex R
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 
 
 -- 
   Alex R
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bulat Ziganshin
Hello Bryan,

Sunday, August 15, 2010, 10:04:01 PM, you wrote:

 shared on Friday, and boiled it down to a simple test case: how long does it 
 take to read a 31MB file?
 GNU wc -m:

there are even slower ways to do it if you need :)

if your data aren't cached, then speed is limited by HDD. if your data
are cached, it should be 20-50x faster. try cat nul


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: String vs ByteString

2010-08-15 Thread Bulat Ziganshin
Hello Daniel,

Sunday, August 15, 2010, 10:39:24 PM, you wrote:

 That's great. If that performance difference is a show stopper, one
 shouldn't go higher-level than C anyway :)

*all* speed measurements that find Haskell is as fast as C, was
broken. Let's see:

D:\testingread MsOffice.arc
MsOffice.arc 317mb -- Done
Time 0.407021 seconds (timer accuracy 0.00 seconds)
Speed 779.505632 mbytes/sec


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe