Re: [Haskell-cafe] Haskell IO and exceptions

2004-12-10 Thread Mark Carroll
On Sun, 5 Dec 2004, Scott Turner wrote: (snip) > Yes. Although Control.Monad.Error forces your error type to be in the Error > class, that puts no constraints on what you save in the errors. If you thread > your errors with the IO Monad then you would be using the monad: >ErrorT YourErrorType I

[Haskell-cafe] Class Synonyms - example 2

2004-12-10 Thread Jorge Adriano Aires
Maybe I should have included a more interesting example in the previous mail. So I had this class: > class Foo a b | a -> b where >foo_method1 :: ... >foo_method2 :: ... >... Besides the case where 'a' is the same as 'b', there is also another interesting case. That is when you have

[Haskell-cafe] Class Synonyms

2004-12-10 Thread Jorge Adriano Aires
Hello! I got a multi-parameter type class: > class Foo a b | a -> b where >foo_method1 :: ... >foo_method2 :: ... >... And some particular cases are important on their own, like the one where 'a' and 'b' are the same, I call elements with this property, Bar. So I defined: class Fo

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Jules Bean
On 10 Dec 2004, at 20:33, GoldPython wrote: Just compiled this with -O and it ran with no stack overflow. Evidently, no `seq` needed for this one. Using ghc 6.2.2. countLines l = countLines' 0 l countLines' n [] = n countLines' n (_:ls) = countLines' (n + 1) ls That's presumably the answer. GHC's s

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Ben Rudiak-Gould
Georg Martius wrote: It was allready posted before, that you need to enforce the evaluation of the + in order to get the function run in constant space. The thing is, that it is harder to achieve than I expected it to be. countLines' ls = foldl (\x y -> let x' = x + 1 in x' `seq` y `seq` x' ) 0

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Stefan Holdermans
Henning, Why is Prelude.length not defined this way (according to the Haskell98 report)? The Report itself answers your question (in Chapter 8): "It constitutes a _specification_ for the Prelude. Many of the definitions are written with clarity rather than efficiency in mind, and it is not requi

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread GoldPython
Just compiled this with -O and it ran with no stack overflow. Evidently, no `seq` needed for this one. Using ghc 6.2.2. countLines l = countLines' 0 l countLines' n [] = n countLines' n (_:ls) = countLines' (n + 1) ls On Fri, 10 Dec 2004 20:32:07 +0100, Georg Martius <[EMAIL PROTECTED]> wrot

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Georg Martius
Hi Will, you probably get confused with stack overflow through non-tail recursive function and stack overflow because you accumulate all intermediate values in the closure. It was allready posted before, that you need to enforce the evaluation of the + in order to get the function run in constan

Re: [Haskell-cafe] hGetLine problem

2004-12-10 Thread Michael Walter
Yeah, I don't see it either why it is affected :) I can try hGetContents from home. Thanks, Michael On Fri, 10 Dec 2004 19:12:39 +, Keean Schupke <[EMAIL PROTECTED]> wrote: > Hmm, I dont see why the main process would be affected... It should be able > to accept multiple connections in para

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread GoldPython
Duh, just read above a bit closer. Sorry for the clutter... On Fri, 10 Dec 2004 13:53:38 -0500, GoldPython <[EMAIL PROTECTED]> wrote: > Thanks to all for the good info. I see what tail recursion is now. > Robert's example above leads me to a couple questions: > > I had actually written my countl

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread GoldPython
I did this: countLines ls = foldl (\x y -> x + 1) 0 ls Still overflows. On Fri, 10 Dec 2004 19:07:04 +0100 (MEZ), Henning Thielemann <[EMAIL PROTECTED]> wrote: > > > > On Fri, 10 Dec 2004, Robert Dockins wrote: > > > >countLines [] = 0 > > >countLines (_:ls) = 1 + countLines ls > >

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread GoldPython
Thanks to all for the good info. I see what tail recursion is now. Robert's example above leads me to a couple questions: I had actually written my countlines like Robert's before the other one I mailed in and mine overflowed the stack just like his. According to people's responses, this one reall

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Jules Bean
On 10 Dec 2004, at 16:35, Ben Rudiak-Gould wrote: Jules Bean wrote: On 10 Dec 2004, at 15:34, Robert Dockins wrote: So it should get "flattened," but it still doesn't run in constant space because the "x" parmeter isn't strict, so it will accumulate a bunch of closures like (((0)+1)+1)+1)+1)+

Re: [Haskell-cafe] hGetLine problem

2004-12-10 Thread Keean Schupke
Hmm, I dont see why the main process would be affected... It should be able to accept multiple connections in parallel. Is it just hGetLine that causes the problem... what if you use hGetContents instead? Does it still not work? (I have a sever implemented - I tested it with "ab -n100 -c10" with no

RE: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Simon Marlow
On 09 December 2004 16:37, Malcolm Wallace wrote: > Robert Dockins <[EMAIL PROTECTED]> writes: > >>> Prelude> [1..5] `zipWith (+)` [7..] >>> :1: parse error on input `(' >> >> is there a technical reason for this or did it just happen? > > If you are asking why general expressions are prohi

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Henning Thielemann
On Fri, 10 Dec 2004, Robert Dockins wrote: > >countLines [] = 0 > >countLines (_:ls) = 1 + countLines ls > > > > I would have thought that this was tail recursive and would be > > flattened into iteration by the compiler. Can anyone explain why? > > countlines = aux 0 > where aux x

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Ben Rudiak-Gould
Henning Thielemann wrote: >I try to stay away from list comprehension because I can't memorize in >which order the conditions are processed [...] I remember it as being slowest-changing-to-the-left, just like the positional notation for integers. E.g. [[x,y] | x <- ['1'..'4'], y <- ['0'..'9']]

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Henning Thielemann
On Fri, 10 Dec 2004, Thomas Johnsson wrote: > > printastable :: [([Int],Word)] -> String > > > > printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ > > "\n") l > > I'd use > > [ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ] > > instead -- after all, list comprehensions

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Ben Rudiak-Gould
Jules Bean wrote: On 10 Dec 2004, at 15:34, Robert Dockins wrote: So it should get "flattened," but it still doesn't run in constant space because the "x" parmeter isn't strict, so it will accumulate a bunch of closures like (((0)+1)+1)+1)+1)+1) To make it strict, do something like this:

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Ben Rudiak-Gould
GoldPython wrote: I know there's "length" to count the elements in a list and it works fine, but the function below stack overflows on a large list. countLines [] = 0 countLines (_:ls) = 1 + countLines ls I would have thought that this was tail recursive and would be flattened into iteration by

Re: [Haskell-cafe] hGetLine problem

2004-12-10 Thread MR K P SCHUPKE
>But if the forkIO'ed process terminates because of an exception, that >shouldn't influence the main process, right? Well, if its unix you might have to set sigPIPE to Ignore... Otherwise, the main process should not die just because the child has... Keean. __

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Jan-Willem Maessen - Sun Labs East
Thomas Johnsson wrote: >>printastable :: [([Int],Word)] -> String >> >>printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ >>"\n") l > > > I'd use > > [ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ] > > instead -- after all, list comprehensions provide a much nicer > synt

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Robert Dockins
Jules Bean wrote: On 10 Dec 2004, at 15:34, Robert Dockins wrote: So it should get "flattened," but it still doesn't run in constant space because the "x" parmeter isn't strict, so it will accumulate a bunch of closures like (((0)+1)+1)+1)+1)+1) To make it strict, do something like this:

Re: [Haskell-cafe] hGetLine problem

2004-12-10 Thread Michael Walter
But if the forkIO'ed process terminates because of an exception, that shouldn't influence the main process, right? - Michael On Fri, 10 Dec 2004 10:18:33 +, Keean Schupke <[EMAIL PROTECTED]> wrote: > What is happening is that the socket is closed after the accept > but before the hGetLine, s

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Jules Bean
On 10 Dec 2004, at 15:34, Robert Dockins wrote: So it should get "flattened," but it still doesn't run in constant space because the "x" parmeter isn't strict, so it will accumulate a bunch of closures like (((0)+1)+1)+1)+1)+1) To make it strict, do something like this: Isn't this what

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Robert Dockins
countLines [] = 0 countLines (_:ls) = 1 + countLines ls I would have thought that this was tail recursive and would be flattened into iteration by the compiler. Can anyone explain why? This function isn't tail recursive, because you do additional operations to the result of the function cal

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Jules Bean
On 10 Dec 2004, at 15:06, GoldPython wrote: I'm missing something, a functional idiom, whatever. I know there's "length" to count the elements in a list and it works fine, but the function below stack overflows on a large list. countLines [] = 0 countLines (_:ls) = 1 + countLines ls I would h

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Thomas Johnsson
> printastable :: [([Int],Word)] -> String > > printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ > "\n") l I'd use [ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ] instead -- after all, list comprehensions provide a much nicer syntax for map, filter and concat. -- Thomas

Re: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Stefan Holdermans
Will, countLines [] = 0 countLines (_:ls) = 1 + countLines ls I would have thought that this was tail recursive and would be flattened into iteration by the compiler. Can anyone explain why? Is it because the call is embedded in an expression? This is the tail-recursive version: \begin{code}

RE: [Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread Bayley, Alistair
http://haskell.org/hawiki/TailRecursive A common technique to make a function tail-recursive is to introduce an accumulating parameter, although in the 5 minutes I've spent looking on the wiki, there's no specific page for this. Perhaps add a link from the Efficiency section on http://haskell.org

[Haskell-cafe] Flattening tail recursion?

2004-12-10 Thread GoldPython
I'm missing something, a functional idiom, whatever. I know there's "length" to count the elements in a list and it works fine, but the function below stack overflows on a large list. countLines [] = 0 countLines (_:ls) = 1 + countLines ls I would have thought that this was tail recursive a

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread MR K P SCHUPKE
Oops, please ignore, I just replied to the wrong emaiL! Keean. ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread MR K P SCHUPKE
At the moment the unix encrypted passwords are downloaded using sov_slave (an application written by ICT that talks directly to the SOV database)... As far as I am aware all unix cluster in college that are part of ICTs single sign-on us this method unless you have recently changed them... I am su

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Josef Svenningsson
On Thu, 09 Dec 2004 10:18:12 -0500, Robert Dockins <[EMAIL PROTECTED]> wrote: > > And I thought that most programmers used "zipWith", which has to be > > prefix. > > Is this true? Can you not use backticks on a partially applied > function? If so, it seems like such a thing would be pretty use

Re: [Haskell-cafe] Non-technical Haskell question

2004-12-10 Thread GoldPython
Well, THERE's two good entries! :^) On Fri, 10 Dec 2004 09:21:21 +0100, Ketil Malde <[EMAIL PROTECTED]> wrote: > > > clearly this guy has never seen Phil Wadler. > > Some people may find this tasteless - I thought it was funny, so I > guess those people will find me tasteless also. In that ca

Re: [Haskell-cafe] hGetLine problem

2004-12-10 Thread Keean Schupke
What is happening is that the socket is closed after the accept but before the hGetLine, so the handle is invalid (there is no socket any more)... This is correct behaviour when the client closes the connection whilst you are writing to it... The answer is just to catch the exception. Keean. Mic

Re: [Haskell-cafe] Parse text difficulty

2004-12-10 Thread Conor McBride
David Menendez wrote: Now that I think about it, you can generalize the trick I mentioned elsewhere to work over any Idiom/Sequence/more-than-a-functor-not-yet-a-monad thingy. Just to fill in the genealogy: the numeral thing is from Daniel Fridlender and Mia Indrika's 'Do we need dependent types?',

[Haskell-cafe] Optimizing common subexpressions [Was: ghc has problems with 'zipWith' ?]

2004-12-10 Thread Henning Thielemann
On Wed, 8 Dec 2004, Derek Elkins wrote: > > Is it possible and senseful for a compiler to extract common > > sub-expressions? Naively I think that for a given tree of an > > expression it is efficiently possible to find all common sub-trees. > > Referential transparency would assure that equal e

Re: [Haskell-cafe] Non-technical Haskell question

2004-12-10 Thread Ketil Malde
> clearly this guy has never seen Phil Wadler. Some people may find this tasteless - I thought it was funny, so I guess those people will find me tasteless also. In that case, I'm probably already in their kill files, so this won't offend anybody. http://www.malevole.com/mv/misc/killer