[Haskell-cafe] Efficiency question

2007-05-30 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 stopD currentD currentN count | currentD  stopD =
count
   | currentN == currentD =
countUniqueFractions stopD (currentD + 1) 1 count
   | canBeSimplified
(currentN, currentD) = countUniqueFractions stopD currentD (currentN+1)
count
   | otherwise =
countUniqueFractions stopD currentD (currentN+1) (count + 1)

When I run this code, I get a stack overflow. I don't understand why. Could
anyone explain please?
-- 
View this message in context: 
http://www.nabble.com/Efficiency-question-tf3823154.html#a10823572
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Efficiency question

2007-05-30 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 (a,b) = gcd a b  1
 
 countUniqueFractions stopD currentD currentN count | currentD  stopD =
 count
| currentN == currentD =
 countUniqueFractions stopD (currentD + 1) 1 count
| canBeSimplified
 (currentN, currentD) = countUniqueFractions stopD currentD (currentN+1)
 count
| otherwise =
 countUniqueFractions stopD currentD (currentN+1) (count + 1)
 
 When I run this code, I get a stack overflow. I don't understand why. Could
 anyone explain please?

Lazy accumulators. Did you try compiling with ghc -O2 ?

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


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]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 negative?

 length $ filter (1) $ Monad.liftM2 gcd [2..1000] [2..1000]
Thanks... now I'll just have to figure out what it does and why it does what
it does.


-- 
View this message in context: 
http://www.nabble.com/Efficiency-question-tf3823154.html#a10873232
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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. How on earth can
 a length be negative?

Yu got an integer overflow - length returns an Int. You can use
Data.List.genericLength  instead, however, which can return its
result in any Num instance. (In particular, Integer works)

 import Data.List
 
 solve :: Integer - Integer
 solve d = genericLength [(y,x) | x - [2..d], y - [1..(x-1)], gcd x y == 1]
 
 main = print (solve 100)

(Note: untested.)

HTH,

Bertram
___
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 Georg Martius
Hi Daniel,
On Fri, 14 Jan 2005 21:57:25 +0100, Daniel Fischer [EMAIL PROTECTED] wrote:
snip
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. AFAIK it is just on the german one.
() :: a - ([a],[b]) - ([a],[b])
x  (xs,ys) = (x:xs,ys)
(§) :: b - ([a],[b]) - ([a],[b])
y § (xs,ys) = (xs,y:ys).
I find them useful (though I don't like the symbols, if you have any better
ideas, thx) and for splitAt, () saves another reduction per step.
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.
 Cheers,
Georg
--
 Georg Martius,  Tel: (+49 34297) 89434 
--- http://www.flexman.homeip.net -
___
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 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:

 snip

  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. AFAIK it is just on the german one.

  () :: a - ([a],[b]) - ([a],[b])
  x  (xs,ys) = (x:xs,ys)
 
  (§) :: b - ([a],[b]) - ([a],[b])
  y § (xs,ys) = (xs,y:ys).
 
  I find them useful (though I don't like the symbols, if you have any
  better ideas, thx) and for splitAt, () saves another reduction per step.

 I think these operators should be more related to : like : : or
Yes, but as Stefan Holdermans already wrote, (:) is illegal (operatornames 
beginning with ':' are infix Constructors). Since I use these operators 
mostly infix (up to now exclusively), I don't really want to type `consfst` 
all the time, hence I would need some stronger argument to convice me of 
using function names (after all, readability is to a large extent a matter of 
familiarity, you couldn't immediately understand ':', '+' ... either if you 
weren't thoroughly familiar with them).

A stronger relation to ':' is absolutely desirable, maybe
something like \: and /: would be better.

Cheers,
Daniel

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


[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 the above, so would it be an improvement to replace n =
 Integerliteral-queries by n  Integerliteral-queries or doesn't
 that make any difference at all in execution time?

I don't know about in Hugs, but in (compiled, optimized) GHC it should
make no difference.  Presumably, if you are running something in an
interpreter micro-optimizing isn't worthwhile.  

 Finally, in several contexts I needed to cons an element to one of a
 pair of lists, so I defined

 infixr 5 ,§
 
 () :: a - ([a],[b]) - ([a],[b])
 x  (xs,ys) = (x:xs,ys)
 
 (§) :: b - ([a],[b]) - ([a],[b])
 y § (xs,ys) = (xs,y:ys).

Well, to start, the type signatures are unnecessarily restrictive. 
Then, the function that also is not in the Report, but does come up
quite a bit by people who get into a point-free or categorical style is
the bifunctor,
(***) :: (a - b) - (c - d) - (a,c) - (b,d)
f *** g = \(a,b) - (f a,g b)
this is an instance of (***) in Control.Arrow, hence the name.

So, your first function is,
() x = (x:) *** id
or using another function from Control.Arrow,
() x = first (x:)

I can say that I have wanted (***), I can't say that I've ever wanted
your two functions.  Also, first (x:) seems to be more self-documenting.
___
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 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 used ([a],[a]) ).
 Then, the function that also is not in the Report, but does come up
 quite a bit by people who get into a point-free or categorical style is
 the bifunctor,
 (***) :: (a - b) - (c - d) - (a,c) - (b,d)
 f *** g = \(a,b) - (f a,g b)
 this is an instance of (***) in Control.Arrow, hence the name.

That's good to know, thanks.

 So, your first function is,
 () x = (x:) *** id
 or using another function from Control.Arrow,
 () x = first (x:)

 I can say that I have wanted (***), I can't say that I've ever wanted
 your two functions.  Also, first (x:) seems to be more self-documenting.

I haven't read Control.Arrow yet, but it seems at first glance that I should 
write
 first (x:) (xs,y)
second (y:) (x,ys)
instead?
That looks good to me, more to type, alas, but much better to read.
Many thanks,
Daniel

___
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
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-z0-9_']*, but does that Haskell report 
define a definitive list of symbols that can be used in Haskell 
source... and how does that relate to the character set... can any 
symbol be used?
___
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 Stefan Holdermans
Keaan,
This reminds me, what symbols are valid for Haskell operators?
See Chapter 9 of the Report [1].
  symbol -  ascSymbol | uniSymbolspecial | _ | : |  | '
  ascSymbol - ! | # | $ | % |  | * | + | . | / |  | = |  | ? | @ | 
\ | ^ | | | - | ~
  uniSymbol - any Unicode symbol or punctuation
  varsym - ( symbol {symbol | :})reservedop | dashes

HTH,
Stefan
[1] http://haskell.org/onlinereport/syntax-iso.html
___
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 | uniSymbolspecial | _ | : |  | '
  ascSymbol - ! | # | $ | % |  | * | + | . | / |  | = |  | ? | @ | 
\ | ^ | | | - | ~
  uniSymbol - any Unicode symbol or punctuation
  varsym - ( symbol {symbol | :})reservedop | dashes

So, does GHC accept more symbols than the report allows? Or would the
example with the sub-section symbol cause an error?
In which case what symbols are allowed in GHC, or Hugs?
   Keean
___
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 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