Re: [Haskell-cafe] Abstracting ByteStrings

2008-01-22 Thread Henning Thielemann
On Tue, 22 Jan 2008, Chad Scherrer wrote: > A lazy ByteString is an alternative to a String=[Char], where > sacrificing some degree of laziness through "chunks" gives much > greater performance in many applications. If I remember correctly, we > could as well create an IntString, DoubleString, et

Re: [Haskell-cafe] announcing darcs 2.0.0pre3

2008-01-22 Thread Bulat Ziganshin
Hello David, Tuesday, January 22, 2008, 11:43:44 PM, you wrote: > The third prerelease features (apart from numerous bug and performance > regression fixes) a completely rewritten rollback command and new > progress-reporting functionality. If darcs takes more than a couple of > seconds for a giv

[Haskell-cafe] haskeem -- (almost) scheme in haskell

2008-01-22 Thread Uwe Hollerbach
Hello, haskellers, I am a total newbie in haskell, but I've been making some mud pies that are coming out kinda pleasingly to my admittedly biased eye. I found Jonathan Tang's excellent tutorial "Write yourself a scheme in 48 hours" a few weeks ago, went through and beyond that, and now have someth

Re: [Haskell-cafe] Draft chapters of "Real World Haskell" now publicly available

2008-01-22 Thread Wolfgang Jeltsch
Am Dienstag, 22. Januar 2008 15:58 schrieb Peter Verswyvelen: > Wow, the full TOC looks very impressive indeed! Maybe add a chapter > about reactive programming (Yampa and Conal's latest stuff that I don't > understand yet) too? :-) > > Cheers, > Peter Covering reactive programming would indeed be

[Haskell-cafe] Re: An idea - Feasibility and effort

2008-01-22 Thread Achim Schneider
Ben Franksen <[EMAIL PROTECTED]> wrote: > Just out of curiosity: how do you plan to find out server locations > (beyond the obvious top-level domain -> country heuristics)? > $ whois | grep Country -- (c) this sig last receiving data processing entity. Inspect headers for past copyright infor

[Haskell-cafe] Re: An idea - Feasibility and effort

2008-01-22 Thread Ben Franksen
Vimal wrote: > Idea 1: > A Traceroute visualizer. > > I saw the video on the London Haskell Group on how to create a game in > Haskell, and loved the "rotating earth" part of the game. (Space > Invaders or something like that). Combine the earth (with a Google > earth touch) with a traceroute back

[Haskell-cafe] Abstracting ByteStrings

2008-01-22 Thread Chad Scherrer
A lazy ByteString is an alternative to a String=[Char], where sacrificing some degree of laziness through "chunks" gives much greater performance in many applications. If I remember correctly, we could as well create an IntString, DoubleString, etc by filling the chunk arrays with different types.

Re: [Haskell-cafe] Precedence and associativity in a pretty-printer

2008-01-22 Thread Allan Clark
Edsko de Vries wrote: Hi, Is there a nice way to pretty-print such an expression with the minimal number of brackets? I can come up with something, but I'm sure somebody thought hard about this problem before and came up with a really nice solution :) Any hints or pointers would be appreciated,

Re: [Haskell-cafe] Precedence and associativity in a pretty-printer

2008-01-22 Thread Ryan Ingram
On 1/22/08, Benja Fallenstein <[EMAIL PROTECTED]> wrote: > Take a look at how Haskell's derived Show instances do it? :-) > > http://www.haskell.org/onlinereport/derived.html#sect10.4 I hate how Haskell handles precedence: 1) Arbitrary magic numbers for precedence, which isn't very natural. 2) Imp

Re: [Haskell-cafe] Irrefutable pattern love and new regex engine.

2008-01-22 Thread Stefan O'Rear
On Tue, Jan 22, 2008 at 02:09:05PM -0800, Ryan Ingram wrote: > > > On Tue, 2008-01-22 at 11:55 -0500, Michael Speer wrote: > > > > rexn ns pps = let ( ~( xs , rps ) , > > > > ~( ~( nxs ) , > > > > ~( rxs , rrps ) ) ) = ( exn nxs pps , >

Re: [Haskell-cafe] Irrefutable pattern love and new regex engine.

2008-01-22 Thread Ryan Ingram
> > On Tue, 2008-01-22 at 11:55 -0500, Michael Speer wrote: > > > rexn ns pps = let ( ~( xs , rps ) , > > > ~( ~( nxs ) , > > > ~( rxs , rrps ) ) ) = ( exn nxs pps , > Not one of the lazy marks was required in the current version. Patte

[Haskell-cafe] announcing darcs 2.0.0pre3

2008-01-22 Thread David Roundy
We are happy to announce the third prerelease version of darcs 2! Darcs 2 features numerous improvements, and it seems that we have fixed most of the regressions, so we're looking for help, from users willing to try this release out. Read below, to see how you can benefit from this new release, and

Re: [Haskell-cafe] Re: ghc6.8: hiding uninstalled package?

2008-01-22 Thread Brandon S. Allbery KF8NH
On Jan 22, 2008, at 14:57 , Ben Franksen wrote: The 'ghc-pkg list dataenc | grep dataenc' cannot be avoided AFAIK. Using some make-fu you can avoid the conditional, though, thus making it a bit more generic: You can also use $(findstring) instead of piping to grep. -- brandon s. allbery

[Haskell-cafe] Re: ghc6.8: hiding uninstalled package?

2008-01-22 Thread Ben Franksen
Magnus Therning wrote: > I stumbled on this behaviour because I was writing a > makefile > for my unit/quickcheck tests. I need to make sure that the correct module > is used, hence I need to hide it if it's installed. I ended up with the > following in order to work around the issue: > > ifeq (

Re: [Haskell-cafe] Irrefutable pattern love and new regex engine.

2008-01-22 Thread Michael Speer
On Jan 22, 2008 11:59 AM, Derek Elkins <[EMAIL PROTECTED]> wrote: > On Tue, 2008-01-22 at 11:55 -0500, Michael Speer wrote: > > I've been using the creation of a regular expression engine as an > > ongoing project to learn Haskell. Last night I created the newest > > iteration. > > > > My love for

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Ian Lynagh
On Tue, Jan 22, 2008 at 03:59:24PM +, Magnus Therning wrote: > > Yes, of course, stupid me. But it is still the UTF-8 representation of "ö", > not Latin-1, and this brings me back to my original question, is this an > intentional change in 6.8? Yes (in 6.8.2, to be precise). It's in the rel

Re: [Haskell-cafe] Precedence and associativity in a pretty-printer

2008-01-22 Thread Benja Fallenstein
Hi Edsko, On Jan 22, 2008 7:34 PM, Edsko de Vries <[EMAIL PROTECTED]> wrote: > Is there a nice way to pretty-print such an expression with the minimal > number of brackets? I can come up with something, but I'm sure somebody > thought hard about this problem before and came up with a really nice >

[Haskell-cafe] Precedence and associativity in a pretty-printer

2008-01-22 Thread Edsko de Vries
Hi, Suppose we have some algebraic datatype describing an expression language containing the usual suspects (various binary arithmetic operators such as addition, subtraction, multiplication, division, exponentiation, function abstraction and application, etc.) each with their own precendence (mul

Re: [Haskell-cafe] Irrefutable pattern love and new regex engine.

2008-01-22 Thread Derek Elkins
On Tue, 2008-01-22 at 11:55 -0500, Michael Speer wrote: > I've been using the creation of a regular expression engine as an > ongoing project to learn Haskell. Last night I created the newest > iteration. > > My love for the irrefutable pattern can be found in the definition of > the rexn ( apply

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Derek Elkins
On Tue, 2008-01-22 at 07:45 -0200, Felipe Lessa wrote: > 2008/1/22 Magnus Therning <[EMAIL PROTECTED]>: > > I vaguely remember that in GHC 6.6 code like this > > > > length $ map ord "a string" > > > > being able able to generate a different answer than > > > > length "a string" > > I guess it

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Jules Bean
Magnus Therning wrote: Yes, of course, stupid me. But it is still the UTF-8 representation of "ö", not Latin-1, and this brings me back to my original question, is this an intentional change in 6.8? > map ord "ö" [246] > map ord "åɓz𝐀" [229,595,65370,119808] 6.8 produces Unicode code point

[Haskell-cafe] Irrefutable pattern love and new regex engine.

2008-01-22 Thread Michael Speer
I've been using the creation of a regular expression engine as an ongoing project to learn Haskell. Last night I created the newest iteration. My love for the irrefutable pattern can be found in the definition of the rexn ( apply repetition to extracted nodes ) function below. /snip rexn ns

Re: [Haskell-cafe] Announce: mersenne-random 0.1, very fast pseudo-random number generation for Haskell

2008-01-22 Thread Don Stewart
gale: > Don Stewart wrote: > > I'm pleased to announce the creation of the mersenne-random package, > > Excellent! We were just discussing that. > > > ...the implementation we bind to is heavily > > impure, so only a single generator is possible per-process (splitting > > generators is also not s

[Haskell-cafe] [Fwd: Invitation for MathematiKa '08 : projectEuler format]

2008-01-22 Thread anshuman
Original Message Subject: Invitation for MathematiKa '08 : projectEuler format From:[EMAIL PROTECTED] Date:Mon, January 21, 2008 11:30 am To: haskell-cafe@haskell.org -

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Peter Verswyvelen
Ian Lynagh wrote: Prelude Data.Char> map ord "ö" [195,182] Prelude Data.Char> length "ö" 2 there are actually 2 bytes there, but your terminal is showing them as one character. So let's all switch to unicode ASAP and leave that horrible multi-byte-string-thing behind us? Cheers, Peter

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Magnus Therning
On 1/22/08, Ian Lynagh <[EMAIL PROTECTED]> wrote: > > On Tue, Jan 22, 2008 at 03:16:15PM +, Magnus Therning wrote: > > On 1/22/08, Duncan Coutts <[EMAIL PROTECTED]> wrote: > > > > > > > > > On Tue, 2008-01-22 at 09:29 +, Magnus Therning wrote: > > > > I vaguely remember that in GHC 6.6 code

Re: [Haskell-cafe] Draft chapters of "Real World Haskell" now publicly available

2008-01-22 Thread Peter Verswyvelen
Wow, the full TOC looks very impressive indeed! Maybe add a chapter about reactive programming (Yampa and Conal's latest stuff that I don't understand yet) too? :-) Cheers, Peter Bryan O'Sullivan wrote: Paul Moore wrote: I'm posting here because there doesn't seem to be an "overall" comm

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Reinier Lamers
Ian Lynagh wrote: On Tue, Jan 22, 2008 at 03:16:15PM +, Magnus Therning wrote: On 1/22/08, Duncan Coutts <[EMAIL PROTECTED]> wrote: On Tue, 2008-01-22 at 09:29 +, Magnus Therning wrote: I vaguely remember that in GHC 6.6 code like this length $ map ord "a string" bei

Re[2]: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Bulat Ziganshin
Hello Duncan, Tuesday, January 22, 2008, 1:36:44 PM, you wrote: > Yes. GHC 6.8 treats .hs files as UTF-8 where it previously treated them > as Latin-1. afair, it was changed since 6.6 -- Best regards, Bulatmailto:[EMAIL PROTECTED]

Re: [Haskell-cafe] Re: Newbie question

2008-01-22 Thread Bulat Ziganshin
Hello Jon, Tuesday, January 22, 2008, 1:04:48 PM, you wrote: >> i.e. you should have other functions that produce A from Integer and >> at the last end this means that class A should provide some way to >> do it > I'm not sure we're using the same terminology. In the > example I gave, the class

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Ian Lynagh
On Tue, Jan 22, 2008 at 03:16:15PM +, Magnus Therning wrote: > On 1/22/08, Duncan Coutts <[EMAIL PROTECTED]> wrote: > > > > > > On Tue, 2008-01-22 at 09:29 +, Magnus Therning wrote: > > > I vaguely remember that in GHC 6.6 code like this > > > > > > length $ map ord "a string" > > > > > >

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Magnus Therning
On 1/22/08, Duncan Coutts <[EMAIL PROTECTED]> wrote: > > > On Tue, 2008-01-22 at 09:29 +, Magnus Therning wrote: > > I vaguely remember that in GHC 6.6 code like this > > > > length $ map ord "a string" > > > > being able able to generate a different answer than > > > > length "a string" >

Re: [Haskell-cafe] Draft chapters of "Real World Haskell" now publicly available

2008-01-22 Thread Paul Moore
On 22/01/2008, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote: > Paul Moore wrote: > > > I'm posting here because there doesn't seem to be an "overall" comment > > section, but the TOC seems to cover less ground than I expected. Is > > the TOC meant to be complete? > > No, it's less than a third of the

Re: [Haskell-cafe] Re: Hangman game

2008-01-22 Thread Yitzchak Gale
Ronald Guida wrote: >> For a Hangman game, the only time I need to change the probability >> distribution is if I load a new word list. If I wanted to be able to >> load a new word list, then perhaps I need to carry the word list >> inside the GameState as well? Achim Schneider wrote: > What abou

Re: [Haskell-cafe] Draft chapters of "Real World Haskell" now publicly available

2008-01-22 Thread Bryan O'Sullivan
Paul Moore wrote: > I'm posting here because there doesn't seem to be an "overall" comment > section, but the TOC seems to cover less ground than I expected. Is > the TOC meant to be complete? No, it's less than a third of the whole thing. Here's the announcement from last May, including a more

Re: [Haskell-cafe] Draft chapters of "Real World Haskell" now publicly available

2008-01-22 Thread Paul Moore
On 21/01/2008, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote: > John, Don and I are pleased to announce the beginning of the public beta > programme for our upcoming book, "Real World Haskell". For further > details, please see the following blog entry: > > http://www.realworldhaskell.org/blog/2008/0

[Haskell-cafe] Re: Hangman game

2008-01-22 Thread Achim Schneider
Ronald Guida <[EMAIL PROTECTED]> wrote: > For a Hangman game, the only time I need to change the probability > distribution is if I load a new word list. If I wanted to be able to > load a new word list, then perhaps I need to carry the word list > inside the GameState as well? > What about carry

Re[2]: [Haskell-cafe] Re: Newbie question

2008-01-22 Thread Bulat Ziganshin
Hello Peter, Tuesday, January 22, 2008, 12:36:49 AM, you wrote: > Hey, I knew about the forall (I use that to represent OO style > collections, very handy), but not about the exists. Thanks. But GHC > 6.8.2 (with -fglasgow-exts) does not seem to accept this "exists" > keyword? > Does a book or

Re[2]: [Haskell-cafe] Yi and Data.ByteString

2008-01-22 Thread Bulat Ziganshin
Hello gwern0, Monday, January 21, 2008, 10:18:15 PM, you wrote: > really built-in - they're a separate library. You could perhaps > suggest that [Char] could be often optimized into ByteString > operations but then ByteStrings need to either lose their library > status and be incorporated into GH

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Duncan Coutts
On Tue, 2008-01-22 at 13:48 +0100, Henning Thielemann wrote: > On Tue, 22 Jan 2008, Duncan Coutts wrote: > > > > At the time I thought that the encoding (in my case UTF-8) was “leaking > > > through”. After switching to GHC 6.8 the behaviour seems to have > > > changed, and mapping 'ord' on a st

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Henning Thielemann
On Tue, 22 Jan 2008, Duncan Coutts wrote: > > At the time I thought that the encoding (in my case UTF-8) was “leaking > > through”. After switching to GHC 6.8 the behaviour seems to have > > changed, and mapping 'ord' on a string results in a list of ints > > representing the Unicode code point

Re: [Haskell-cafe] Announce: mersenne-random 0.1, very fast pseudo-random number generation for Haskell

2008-01-22 Thread Yitzchak Gale
Don Stewart wrote: > I'm pleased to announce the creation of the mersenne-random package, Excellent! We were just discussing that. > ...the implementation we bind to is heavily > impure, so only a single generator is possible per-process (splitting > generators is also not supported)... > Note th

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Duncan Coutts
On Tue, 2008-01-22 at 12:56 +0300, Miguel Mitrofanov wrote: > > > chr . ord $ 'å' > > '\229' > > What would I have to do to get an 'å' from '229'? > > It seems you already have it; 'å' is the same as '\229'. Yes. > But IO output is still 8-bit, so when you ask ghci to print 'å', you get >

Re: [Haskell-cafe] non-alphabetical mathematical symbols as non-infix function names

2008-01-22 Thread Duncan Coutts
On Tue, 2008-01-22 at 07:03 +0100, Cetin Sert wrote: > (¬) :: Bool → Bool > (¬) q = not q > > q = True > ¬ q : parser error on input > q ¬ : parser error (possibly incorrect indentation) > (¬ q) : Couldn't match expected type `Bool -> t' against inferred type > `Bool' In the expression: (� True)

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Duncan Coutts
On Tue, 2008-01-22 at 09:29 +, Magnus Therning wrote: > I vaguely remember that in GHC 6.6 code like this > > length $ map ord "a string" > > being able able to generate a different answer than > > length "a string" That seems unlikely. > At the time I thought that the encoding (in my

Re: [Haskell-cafe] Hamming's Problem

2008-01-22 Thread Bertram Felgenhauer
I wrote: > merge' (x:xs) ys = x : merge xs ys > > hammingx = 1 : foldr1 merge' [map (h x) hammingx | x <- hammingx] Sorry. 'foldr1' is still slightly too strict. (Why doesn't the Haskell report define foldr1 in terms of foldr?) The code that works is marge' [] ys = ys merge

[Haskell-cafe] Re: Newbie question

2008-01-22 Thread Jon Fairbairn
Bulat Ziganshin <[EMAIL PROTECTED]> writes: > Hello Jon, > > Monday, January 21, 2008, 9:28:09 PM, you wrote: > >>> Ok. I have a my own class "class A a" and want to write function like >>> this "f:: (A a)=>Integer->a". Can I do it? > >> But in general you are going to want something a bit more >

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Miguel Mitrofanov
> > chr . ord $ 'å' > '\229' > What would I have to do to get an 'å' from '229'? It seems you already have it; 'å' is the same as '\229'. But IO output is still 8-bit, so when you ask ghci to print 'å', you get '\229'. You can use utf-string library (from hackage). __

Re: [Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Felipe Lessa
2008/1/22 Magnus Therning <[EMAIL PROTECTED]>: > I vaguely remember that in GHC 6.6 code like this > > length $ map ord "a string" > > being able able to generate a different answer than > > length "a string" I guess it's not very difficult to prove that ∀ f xs. length xs == length (map

[Haskell-cafe] Has character changed in GHC 6.8?

2008-01-22 Thread Magnus Therning
I vaguely remember that in GHC 6.6 code like this length $ map ord "a string" being able able to generate a different answer than length "a string" At the time I thought that the encoding (in my case UTF-8) was “leaking through”. After switching to GHC 6.8 the behaviour seems to have chang