Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Bertram Felgenhauer
Evil Bro wrote: > > > Counting can be done elegantly by 'filter' and 'length': > I figured out the following code after posting: > > solve d = length [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1] > main = print (solve 100) > > However when running it, it gave an answer of -1255316543.

Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Evil Bro
> Counting can be done elegantly by 'filter' and 'length': I figured out the following code after posting: solve d = length [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1] main = print (solve 100) However when running it, it gave an answer of -1255316543. How on earth can a length be ne

Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Henning Thielemann
On Sun, 27 May 2007, Evil Bro wrote: > I'm pretty new to Haskell, so forgive me if my question is due to my > non-functional way of thinking... > > I have the following code: Counting can be done elegantly by 'filter' and 'length': length $ filter (>1) $ Monad.liftM2 gcd [2..1000] [2..1000] ___

Re: [Haskell-cafe] Efficiency question

2007-05-29 Thread Donald Bruce Stewart
rwiggerink: > > I'm pretty new to Haskell, so forgive me if my question is due to my > non-functional way of thinking... > > I have the following code: > > module Main where > > main = print solution > > solution = solve 100 > > solve d = countUniqueFractions d 2 1 0 > > canBeSimplified

[Haskell-cafe] Efficiency question

2007-05-29 Thread Evil Bro
I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking... I have the following code: module Main where main = print solution solution = solve 100 solve d = countUniqueFractions d 2 1 0 canBeSimplified (a,b) = gcd a b > 1 countUniqueFractions

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Stefan Holdermans
Keaan, (§) :: b -> ([a],[b]) -> ([a],[b]) y § (xs, ys) = (xs,y:ys) GHC gives a lexical error. Regards, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Keean Schupke
Stefan Holdermans wrote: symbol -> ascSymbol | uniSymbol ascSymbol -> ! | # | $ | % | & | * | + | . | / | < | = | > | ? | @ | \ | ^ | | | - | ~ uniSymbol -> any Unicode symbol or punctuation varsym -> ( symbol {symbol | :}) So, does GHC accept more symbols than the report allows? Or woul

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Stefan Holdermans
Keaan, This reminds me, what symbols are valid for Haskell operators? See Chapter 9 of the Report [1]. symbol -> ascSymbol | uniSymbol ascSymbol -> ! | # | $ | % | & | * | + | . | / | < | = | > | ? | @ | \ | ^ | | | - | ~ uniSymbol -> any Unicode symbol or punctuation varsym -> ( symbol {

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Keean Schupke
Georg Martius wrote: infixr 5 &,§ ^^^ Please be aware that you won't find this paragraph symbol on a uk or us keyboard. AFAIK it is just on the german one. This reminds me, what symbols are valid for Haskell operators? I know that function names are: (in regex format) [A-Za-z_'][A-Za-

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Daniel Fischer
Am Samstag, 15. Januar 2005 14:36 schrieben Sie: > Well, to start, the type signatures are unnecessarily restrictive. Yep, but since I always needed them for taking elements that satisfied either of two predicates from a list, that was the type that first came to mind (actually the zero'th type

[Haskell-cafe] Efficiency Question

2005-01-15 Thread Derek Elkins
> Another thing, while toying, I found out that a comparison (n <= 0) > takes three reductions more than (n < 1) according to my hugs, so > changing the definition of splitAt thus, we require (3*n) reductions > less. But the number of reductions and speed are different things, as > witnessed by th

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Daniel Fischer
Am Samstag, 15. Januar 2005 10:05 schrieben Sie: > Hi Daniel, > > On Fri, 14 Jan 2005 21:57:25 +0100, Daniel Fischer > <[EMAIL PROTECTED]> wrote: > > > > > Finally, in several contexts I needed to cons an element to one of a pair > > of lists, so I defined > > > > infixr 5 &,§ >^^^

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Stefan Holdermans
Georg, I think these operators should be more related to ":" like ":&" "&:" or similar. However, in my opinion this special cons operators could be just functions with a meaningful name like "consfst" and "conssnd". It would provide much more readability. And (:&) would of course be illegal anyw

Re: [Haskell-cafe] Efficiency Question

2005-01-15 Thread Georg Martius
Hi Daniel, On Fri, 14 Jan 2005 21:57:25 +0100, Daniel Fischer <[EMAIL PROTECTED]> wrote: Finally, in several contexts I needed to cons an element to one of a pair of lists, so I defined infixr 5 &,§ ^^^ Please be aware that you won't find this paragraph symbol on a uk or us keyboard.

Re: [Haskell-cafe] Efficiency Question

2005-01-14 Thread Tom Pledger
Daniel Fischer wrote: [snip] Another thing, while toying, I found out that a comparison (n <= 0) takes three reductions more than (n < 1) according to my hugs, so changing the definition of splitAt thus, we require (3*n) reductions less. That difference looks like it comes from the default defin

[Haskell-cafe] Efficiency Question

2005-01-14 Thread Daniel Fischer
Hi folks, toying a bit with splitAt and take, I have met yet another thing, I don't understand. In the Hugs Prelude, splitAt is defined splitAt n xs | n <= 0 = ( [],xs) splitAt _ [] = ([],[]) splitAt n (x:xs)= (x:xs',xs'') where (xs',xs'') = splitAt (n-1) xs whereas in the