[Haskell-cafe] Re: ANNOUNCE: GHC version 6.8.2

2007-12-21 Thread Judah Jacobson
I neglected to CC the below email to haskell-cafe; apologies if anyone gets this twice. -- Forwarded message -- From: Judah Jacobson <[EMAIL PROTECTED]> Date: Dec 21, 2007 2:12 PM Subject: Re: [Haskell-cafe] Re: ANNOUNCE: GHC version 6.8.2 To: John Dorsey <[EMAIL PROTECTED]> On D

Re: readline problems building GHC on Mac OS X (was: Re: [Haskell-cafe] Re: ANNOUNCE: GHC version 6.8.2)

2007-12-21 Thread Deborah Goldsmith
On Dec 21, 2007, at 3:40 PM, Thorkil Naur wrote: 1. Which readline do we use? GNU readline, of course. As opposed to the readline installed as /usr/include/readline/*.h and /usr/lib/libreadline.dylib on our PPC Mac OS X machines which are said to be (and can even be observed to be) symbolic

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Stefan O'Rear
On Fri, Dec 21, 2007 at 03:16:17PM -0800, David Benbennick wrote: > On Dec 21, 2007 2:30 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > > dbenbenn: > > > Thanks for fixing this. But doesn't GHC have strictness analysis? > > > > Sure does! > > > > The problem here was an explicit recusive loop though

readline problems building GHC on Mac OS X (was: Re: [Haskell-cafe] Re: ANNOUNCE: GHC version 6.8.2)

2007-12-21 Thread Thorkil Naur
Hello, Although I have been building various GHC versions on various PPC Mac OS X systems for a while now, I'm afraid that I don't really have a good answer for your questions. However, your questions provide an excellect opportunity to discuss this, so that is what I am going to do. There are

Re: [Haskell-cafe] Optimizing cellular automata & the beauty of unlifted types

2007-12-21 Thread Justin Bailey
On Dec 21, 2007 2:55 PM, Bertram Felgenhauer <[EMAIL PROTECTED]> wrote: > > If you look at the generated machine code, you'll find that f and g > are identical functions. The sole purpose of the int2Word# and > word2Int# operations is to satisfy the type checker. (This is > even true at the core l

Re: [Haskell-cafe] eager/strict eval katas

2007-12-21 Thread Thomas Hartman
great advice. I played with this a bit, desugared to haskell 98, and got -- okay for 1..10^6, not ok (stack overflows) if either the fold or g is left lazy. -- Thanks, Dan Weston. avg6 = uncurry (/) . foldl' g (0,0) where g (!sum,!count) next = ( (sum+next),(count+1)) -- same thing, in haskell98

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread David Benbennick
On Dec 21, 2007 2:30 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > dbenbenn: > > Thanks for fixing this. But doesn't GHC have strictness analysis? > > Sure does! > > The problem here was an explicit recusive loop though, > with just not enough for the strictness analyser to get going. The explicit

Re: [Haskell-cafe] Optimizing cellular automata & the beauty of unlifted types

2007-12-21 Thread Bertram Felgenhauer
Justin Bailey wrote: > On Dec 20, 2007 7:42 PM, Sterling Clover <[EMAIL PROTECTED]> wrote: > > I'm curious how much of the unboxing helped performance and how much > > didn't. In my experience playing with this stuff, GHC's strictness > > analyzer has consistently been really excellent, given the r

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Don Stewart
dbenbenn: > On Dec 21, 2007 12:02 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > > There's no good reason for the accumulator for Integer to be lazy, > > especially when you see that adding an upper bound (enumFromTo) or > > using Int uses a strict accumulator. > > > > I've filled a bug report and f

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread David Benbennick
On Dec 21, 2007 12:02 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > There's no good reason for the accumulator for Integer to be lazy, > especially when you see that adding an upper bound (enumFromTo) or > using Int uses a strict accumulator. > > I've filled a bug report and fix for this. > > h

Re: [Haskell-cafe] Re: Haskell performance

2007-12-21 Thread Isaac Dupree
Jon Harrop wrote: On Thursday 20 December 2007 19:02, Don Stewart wrote: Ok, so I should revive nobench then, I suspect. http://www.cse.unsw.edu.au/~dons/nobench/x86_64/results.html that kind of thing? Many of those benchmarks look good. However, I suggest avoiding trivially reducible p

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread David Menendez
On Dec 21, 2007 2:38 PM, Jules Bean <[EMAIL PROTECTED]> wrote: > David Menendez wrote: > >> That's a reasonable thing to assume. It just happens that Haskell > > doesn't work that way. There's an asymmetry between constructing and > > pattern-matching, and it's one that many people have complained

[Haskell-cafe] Re: ANNOUNCE: GHC version 6.8.2

2007-12-21 Thread John Dorsey
(Moving to the cafe) On a related topic, I've been trying to build 6.8.2 on Leopard lately. I've been running up against the infamous OS X readline issues. I know some builders here have hacked past it, but I'm looking for a good workaround... ideally one that works without changes outside the GH

[Haskell-cafe] Re: functional maps

2007-12-21 Thread Chad Scherrer
Chad Scherrer gmail.com> writes: > > A while back I was playing with Data.Map was getting irritated about > lookups that fail having the type of values, but wrapped in an extra > monad. I decided to work around this by putting a default in the data > type itself, so we have a "functional map" >

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Don Stewart
coeus: > Am Freitag, 21. Dezember 2007 schrieb Justin Bailey: > > Given this function: > > > > dropTest n = head . drop n $ [1..] > > > > I get a stack overflow when n is greater than ~ 550,000 . Is that > > inevitable behavior for large n? Is there a better way to do it? > > > > Justin > > [

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Marc A. Ziegert
Am Freitag, 21. Dezember 2007 schrieb Justin Bailey: > Given this function: > > dropTest n = head . drop n $ [1..] > > I get a stack overflow when n is greater than ~ 550,000 . Is that > inevitable behavior for large n? Is there a better way to do it? > > Justin [1..] equals [1, (1)+1, (1+1)+

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Jules Bean
David Menendez wrote: That's a reasonable thing to assume. It just happens that Haskell doesn't work that way. There's an asymmetry between constructing and pattern-matching, and it's one that many people have complained about. With GADTs turned on (-XGADTS in 6.8, -fglasgow-exts in 6.6) patte

Re: [Haskell-cafe] Optimizing cellular automata & the beauty of unlifted types

2007-12-21 Thread Felipe Lessa
On Dec 21, 2007 3:00 PM, Justin Bailey <[EMAIL PROTECTED]> wrote: > It really did help. I started with an implementation that used Ints, > and this sped the program up by at least 2x. I think that's because of > the bit-manipulation I'm doing. For example, Data.Bits defines the > bitwise and operat

[Haskell-cafe] functional maps

2007-12-21 Thread Chad Scherrer
A while back I was playing with Data.Map was getting irritated about lookups that fail having the type of values, but wrapped in an extra monad. I decided to work around this by putting a default in the data type itself, so we have a "functional map" data FMap k a = FMap (k -> a) (Map k a) This h

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread David Menendez
On Dec 21, 2007 12:08 PM, Nicholls, Mark <[EMAIL PROTECTED]> wrote: > I thought from > > > > "Num numberType => SquareConstructor > numberType" > > > > We could deduce that (in English rather than get Haskell and FOL > confusion) > > > > all values of "SquareConstructor a"….the type of a would ha

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread David Menendez
On Dec 21, 2007 12:47 PM, Nicholls, Mark <[EMAIL PROTECTED]> wrote: > Let me resend the code…as it stands…. > > > > *module* Main *where* > > > > *data* SquareType numberType = Num numberType => SquareConstructor > numberType > > > > *class* ShapeInterface shape *where* > > area :: Num numb

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Don Stewart
derek.a.elkins: > On Fri, 2007-12-21 at 09:56 -0800, David Benbennick wrote: > > On Dec 21, 2007 9:51 AM, Justin Bailey <[EMAIL PROTECTED]> wrote: > > > I think its [1..] which is building up the unevaluated thunk. Using > > > this definition of dropTest does not blow the stack: > > > > It also wo

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Miguel Mitrofanov
module Main where data SquareType numberType = Num numberType => SquareConstructor numberType class ShapeInterface shape where area :: Num numberType => shape->numberType data ShapeType = forall a. ShapeInterface a => ShapeType a instance (Num a) => ShapeInterface (SquareType

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Derek Elkins
On Fri, 2007-12-21 at 09:56 -0800, David Benbennick wrote: > On Dec 21, 2007 9:51 AM, Justin Bailey <[EMAIL PROTECTED]> wrote: > > I think its [1..] which is building up the unevaluated thunk. Using > > this definition of dropTest does not blow the stack: > > It also works if you do [(1::Int) ..]

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Albert Y. C. Lai
Justin Bailey wrote: Given this function: dropTest n = head . drop n $ [1..] I get a stack overflow when n is greater than ~ 550,000 . Is that inevitable behavior for large n? Is there a better way to do it? Just for fun, throw in dropTest :: Int -> Int and experiment again! :)

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread David Benbennick
On Dec 21, 2007 9:51 AM, Justin Bailey <[EMAIL PROTECTED]> wrote: > I think its [1..] which is building up the unevaluated thunk. Using > this definition of dropTest does not blow the stack: It also works if you do [(1::Int) ..] !! n, but not with [(1::Integer) ..] !! n Sounds like GHC is being s

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Justin Bailey
On Dec 21, 2007 9:48 AM, Brad Larsen <[EMAIL PROTECTED]> wrote: > I'm curious as well. My first thought was to try the (!!) operator. > Typing > >Prelude> [1..] !! 55 > > overflows the stack on my computer, as does dropTest 55. I think its [1..] which is building up the unevaluated th

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Brad Larsen
On Fri, 21 Dec 2007 12:13:04 -0500, Justin Bailey <[EMAIL PROTECTED]> wrote: Given this function: dropTest n = head . drop n $ [1..] I get a stack overflow when n is greater than ~ 550,000 . Is that inevitable behavior for large n? Is there a better way to do it? Justin I'm curious as w

RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Let me resend the code...as it stands module Main where data SquareType numberType = Num numberType => SquareConstructor numberType class ShapeInterface shape where area :: Num numberType => shape->numberType data ShapeType = forall a. ShapeInterface a => ShapeType a

RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Yes sorrybut this still fails with "`numberType1' is a rigid type variable bound by" From: Brent Yorgey [mailto:[EMAIL PROTECTED] Sent: 21 December 2007 17:29 To: Nicholls, Mark Cc: Jules Bean; haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] n

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Brent Yorgey
> > "class ShapeInterface shape where >area :: shape->Int" > > now looks dubiousI want it to be something like > > "class ShapeInterface shape where >area :: Num numberType => shape->Int" ? > Rather, I think you probably want class ShapeInterface shape where area :: Num nu

Re: [Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Derek Elkins
On Fri, 2007-12-21 at 09:13 -0800, Justin Bailey wrote: > Given this function: > > dropTest n = head . drop n $ [1..] > > I get a stack overflow when n is greater than ~ 550,000 . Is that > inevitable behavior for large n? Is there a better way to do it? A similar example is discussed on http:

[Haskell-cafe] Why does this blow the stack?

2007-12-21 Thread Justin Bailey
Given this function: dropTest n = head . drop n $ [1..] I get a stack overflow when n is greater than ~ 550,000 . Is that inevitable behavior for large n? Is there a better way to do it? Justin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org h

[Haskell-cafe] FFI"pointer" data types question

2007-12-21 Thread Galchin Vasili
Hi, If I am calling a ANSI function that requires a pointer to a C struct, which FFI pointer type should use? Kind regards, Vasya ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Oh You are correct... I thought from "Num numberType => SquareConstructor numberType" We could deduce that (in English rather than get Haskell and FOL confusion) all values of "SquareConstructor a"the type of a would have be be in class Num?.. is this not correct?

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread David Menendez
On Dec 21, 2007 11:50 AM, Nicholls, Mark <[EMAIL PROTECTED]> wrote: > Now I have > > module Main where > > data SquareType numberType = Num numberType => SquareConstructor > numberType This is a valid declaration, but I don't think it does what you want it to. The constraint on numberType ap

Re: [Haskell-cafe] Optimizing cellular automata & the beauty of unlifted types

2007-12-21 Thread Justin Bailey
On Dec 20, 2007 7:42 PM, Sterling Clover <[EMAIL PROTECTED]> wrote: > I'm curious how much of the unboxing helped performance and how much > didn't. In my experience playing with this stuff, GHC's strictness > analyzer has consistently been really excellent, given the right > hints. Unboxed tuples

RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
Now I have module Main where data SquareType numberType = Num numberType => SquareConstructor numberType data RectangleType = RectangleConstructor Int Int class ShapeInterface shape where area :: shape->Int data ShapeType = forall a. ShapeInterface a => ShapeType a instance ShapeI

RE: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
ReallyI'm sure I tried that...(as it seemed obvious) ... and it failedbut I'll have another go -Original Message- From: Jules Bean [mailto:[EMAIL PROTECTED] Sent: 21 December 2007 15:33 To: Nicholls, Mark Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] nice simple pro

[Haskell-cafe] Re: How to make Prelude.read: no parse more verbose ...

2007-12-21 Thread Georg Sauthoff
Ketil Malde <[EMAIL PROTECTED]> wrote: > Georg Sauthoff <[EMAIL PROTECTED]> writes: >> Well, how do I compile a Haskell program in such a way, that I >> get a useful error message from read? I mean, like the >> filename/linenumber of the calling expression for starters. > It's dirty, it's mean, b

[Haskell-cafe] Re: MonadFix

2007-12-21 Thread Joost Behrends
apfelmus quantentunnel.de> writes: > Huh? p < intsqrt n is evaluated just as often as p*p > n , with > changing n . Why would that be less expensive? Btw, the code above > test for r==0 first, which means that the following p*p > n is > tested exactly once for every prime candidate p

[Haskell-cafe] Re: MonadFix

2007-12-21 Thread apfelmus
Daniel Fischer wrote: apfelmus writes: | r == 0= p : f (p:ps) q | p*p > n = [n] | otherwise = f ps n However, when you do the sensible thing (which Joost did) and have the intsqrt a parameter of the function, like in factorize :: Integer -> [Integer] factor

Re: [Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Jules Bean
Nicholls, Mark wrote: *instance* ShapeInterface SquareType *where* area (SquareConstructor sideLength) = sideLength * sideLength *data* SquareType a = Num a => SquareConstructor a Now you have changed your type from SquareType to SquareType a, you need to change the instance to:

[Haskell-cafe] nice simple problem for someone struggling....

2007-12-21 Thread Nicholls, Mark
I'm just trying to pick up the basicsand I've managed to write this code...which remarkably works.. module Main where data SquareType = SquareConstructor Int class ShapeInterface shape where area :: shape->Int data ShapeType = forall a. ShapeInterface a => Shape

Re: [Haskell-cafe] Re: announcing darcs 2.0.0pre2

2007-12-21 Thread David Roundy
On Mon, Dec 17, 2007 at 12:29:20PM +, Simon Marlow wrote: > David Roundy wrote: > >I am pleased to announce the availability of the second prerelease of darcs > >two, darcs 2.0.0pre2. > > Thanks! > > Continuing my performance tests, I tried unpulling and re-pulling a bunch > of patches in a

[Haskell-cafe] Re: MonadFix

2007-12-21 Thread Joost Behrends
@apfelmus, please read my code. I introduced DivIter to separate divstep from divisions. But it stores intsqrt dividend also. Thus the sqrt is only recomputed, when a new factor is found. Concerning primes': With the sieve of Eratosthenes we cannot make a lazy list, we need the whole list at any

[Haskell-cafe] Re: MonadFix

2007-12-21 Thread Joost Behrends
@apfelmus, please read my code. I introduced DivIter to separate divstep from divisions. But it stores intsqrt dividend also. Thus the sqrt is only recomputed, when a new factor is found. Concerning primes': With the sieve of Eratosthenes we cannot make a lazy list, we need the whole list at any

Re: [Haskell-cafe] Re: MonadFix

2007-12-21 Thread Daniel Fischer
Am Freitag, 21. Dezember 2007 11:33 schrieb apfelmus: > Joost Behrends wrote: > > apfelmus writes: > >> How about separating the candidate prime numbers from the recursion > >> > >>factorize :: Integer -> [Integer] > >>factorize = f primes' > >> where > >> primes' = 2:[3,5..] >

[Haskell-cafe] Applying a Dynamic function to a container of Dynamics

2007-12-21 Thread Alfonso Acosta
Hi all, dynApp allows to apply a Dynamic function to a Dynamic argument: dynApp :: Dynamic -> Dynamic -> Dynamic I don't seem to find a way (without modifying Data.Dynamic itself) to code this function import Data.Typeable import Data.Dynamic import Data.Foldable dynApp1 :: (Typeable1 containe

Re: [Haskell-cafe] Smart Constructor Puzzle

2007-12-21 Thread Henning Thielemann
On Thu, 20 Dec 2007, Stefan O'Rear wrote: > On Thu, Dec 20, 2007 at 11:39:42PM -0500, Ronald Guida wrote: > > > data PZero = PZero deriving (Show) > > > data PSucc a = PSucc a deriving (Show) > > > > > > type P1 = PSucc PZero > > > type P2 = PSucc P1 > > > type P3 = PSucc P2 > > > -- etc > >

[Haskell-cafe] Re: Dynamic typing of polymorphic functions

2007-12-21 Thread Alfonso Acosta
Hi Oleg! Thanks a lot for your answer, you turn out to end up solving every problem I get stuck in :) This bit was the essential part of it. On Dec 20, 2007 11:47 AM, <[EMAIL PROTECTED]> wrote: > -- it is important to give the signature to (,) below: we pack the cons > -- function of the right

[Haskell-cafe] Re: MonadFix

2007-12-21 Thread apfelmus
Joost Behrends wrote: apfelmus writes: How about separating the candidate prime numbers from the recursion factorize :: Integer -> [Integer] factorize = f primes' where primes' = 2:[3,5..] f (p:ps) n | r == 0= p : f (p:ps) q | p*p > n = [n]

Re: [Haskell-cafe] Re: MonadFix

2007-12-21 Thread Ryan Ingram
On 12/20/07, Joost Behrends <[EMAIL PROTECTED]> wrote: > > The syntax with the block in > > "newtype State s a = State { runState :: s -> (a,s) }" > > is not in the tutorials i read. newtype creates a new type which is treated exactly the same as an existing type at runtime, but which is distinct

Re: FFI question -- was: [Haskell-cafe] New slogan for haskell.org

2007-12-21 Thread Gour
On Thu, 20 Dec 2007 03:41:21 + Duncan Coutts <[EMAIL PROTECTED]> wrote: > The main advantage of c2hs over hsc2hs is that c2hs generates the > correct Haskell types of foreign imports by looking at the C types in > the header file. This guarantees cross language type safety for > function calls