RE: Finding primes using a primes map with Haskell and Hugs98

2000-12-20 Thread Shlomi Fish

On Tue, 19 Dec 2000, Simon Peyton-Jones wrote:

> | Another way to do this is to compute the final array directly,
> | instead of computing successive versions of the array:
> | 
> | import Array
> | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
> | primesMap   = accumArray (||) False (2,n) multList
> | multList= [(m,True) | j <- [2 .. n `div` 2], m <- 
> | multiples j]
> | multiples j = takeWhile (n>=) [k*j | k <- [2..]]
> 
> This style is definitely the way to go.  Haskell does badly
> if you update an array one index at a time.  
> 

Unfortunately, it seems that this style is not the way to go. This program
cannot scale beyond 5000 while my second program scales beyond 3. I'm
not saying 3 is a good limit, but 5000 is much worse.

Anyway, somebody who contacted me in private suggested the following
method. It is a similiar algorithm which uses a list instead of an array.


primes :: Int -> [Int]

primes how_much = sieve [2..how_much] where
 sieve (p:x) = 
 p : (if p <= mybound
 then sieve (remove (p*p) x)
 else x) where
 remove what (a:as) | what > how_much = (a:as)
| a < what = a:(remove what as)
| a == what = (remove (what+step) as)
| a > what = a:(remove (what+step) as)
 remove what [] = []
 step = (if (p == 2) then p else (2*p)) 
 sieve [] = []
 mybound = ceiling(sqrt(fromIntegral how_much))

I optimized it quite a bit, but the concept remained the same. 

Anyway, this code can scale very well to 10 and beyond. But it's not
exactly the same algorithm.

I also implemented this algorithm in perl, and I can send it in person if
anybody requests it.

I'll try to see how the two programs run in GHC and HBC.

Regards,

Shlomi Fish




> Remember that arrays can be recursive.  Here's a definition
> of Fibonacci for example; you can probably adapt it for primes
> 
> fibs :: Int -> Array Int Int
> -- If a = fibs n, then a!i is fib(i), for i<=n.
> fibs n = a
>   where
>a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <-
> [3..n]])
>   -- Notice that a is recursive
> 
> Simon
> 
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 



--
Shlomi Fish[EMAIL PROTECTED] 
Home Page: http://t2.technion.ac.il/~shlomif/
Home E-mail:   [EMAIL PROTECTED]

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Finding primes using a primes map with Haskell and Hugs98

2000-12-20 Thread George Russell

There are numerous ways of optimising sieving for primes, none of which have much
to do with this list.  For example, two suggestions:
(1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise
sieve separately for this k on higher primes.  (Or you might use products of
more or less primes, depending on memory and how high you were going.)
(2) use bitwise arithmetic.
If you look in the literature I think you'll find plenty more possibilities.
I don't really see why any of this has anything to do with Haskell though.
When it comes to seriously icky bit-twiddling algorithms I don't think Haskell
has much to offer over C, especially as you'd have to make everything unboxed if
you want comparable speed.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Finding primes using a primes map with Haskell and Hugs98

2000-12-20 Thread Colin . Runciman

> There are numerous ways of optimising sieving for primes, none of which
> have much to do with this list.  For example, two suggestions:
> (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise
> sieve separately for this k on higher primes.  (Or you might use products of
> more or less primes, depending on memory and how high you were going.)
> ...
> I don't really see why any of this has anything to do with Haskell though.
> When it comes to seriously icky bit-twiddling algorithms I don't think Haskell
> has much to offer over C, especially as you'd have to make everything unboxed if
> you want comparable speed.

Forgive the self-reference, but the following short article is
all about this very topic:

C. Runciman,
Lazy wheel sieves and spirals of primes,
Journal of Functional Programming, v7, n2, pp219--226,
March 1997.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Haskell Productivity

2000-12-20 Thread Steinitz, Dominic J

The Haskell website claims that

"Ericsson measured an improvement factor of between 9 and 25 in one set of experiments 
on telephony software".

Presumably this is with Erlang not with Haskell. I have searched for the reference 
that substantiates this claim but I've only been able to find:

http://set.gmd.de/~ap/femsys/wiger.html 

which talks about a productivity factor of 4

and

http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haskell-vs-ada-abstract.html

which suggests that Haskell is about 2-3 times as productive as imperative languages.

Can someone point me at some more references? Especially the one that talks about a 
productivity improvement of 9-25?

Thanks, Dominic.

-
21st century air travel http://www.britishairways.com

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Problem with functional dependencies

2000-12-20 Thread Simon Peyton-Jones

I think you can simplify the example.  Given

class HasFoo a b | a -> b where
  foo :: a -> b

instance HasFoo Int Bool where ...

Is this legal?

f :: HasFoo Int b => Int -> b
f x = foo x

You might think so, since 
HasFoo Int b => Int -> b
is a substitution instance of
HasFoo a b => a -> b

but if we infer the type (HasFoo Int b => Int -> b)
for f's RHS, we can then "improve" it using the instance
decl to (HasFoo Int Bool => Int -> Bool), and now the signature
isn't a substitution insance of the type of the RHS.  Indeed,
this is just what will happen if you try with GHC, because
GHC takes advantage of type signatures when typechecking a 
function defn, rather than first typechecking the defn and only
then comparing with the signature.

I don't know what the answers are here, but there's more to this
functional dependency stuff than meets the eye.  Even whether
one type is more general than another has changed!

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]]
| Sent: 17 December 2000 19:30
| To: [EMAIL PROTECTED]
| Subject: Problem with functional dependencies
| 
| 
| The following module is rejected by both
| ghc -fglasgow-exts -fallow-undecidable-instances
| and
| hugs -98
| 
| --
| --
| class HasFoo a foo | a -> foo where
| foo :: a -> foo
| 
| data A = A Int
| data B = B A
| 
| instance HasFoo A Int where
| foo (A x) = x
| 
| instance HasFoo A foo => HasFoo B foo where
| foo (B a) = foo a
| --
| --
| 
| The error messsage says that the type inferred for foo in B's instance
| is not general enough: the rhs has type "HasFoo B Int => B -> 
| Int", but
| "HasFoo B foo => B -> foo" was expected.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell Productivity

2000-12-20 Thread Paul Hudak

> Can someone point me at some more references?

See http://haskell.org/papers/NSWC/jfp.ps.

  -Paul

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Haskell Productivity

2000-12-20 Thread Peter Douglass

There is a thread on comp.lang.functional which may be of interest.
Here is a link that might work for you.

http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh
8ss$6le$[EMAIL PROTECTED]%3e%231/1

> -Original Message-
> From: Steinitz, Dominic J 
> [mailto:[EMAIL PROTECTED]]
> Sent: Wednesday, December 20, 2000 11:12 AM
> To: haskell
> Subject: Haskell Productivity
> 
> 
> The Haskell website claims that
> 
> "Ericsson measured an improvement factor of between 9 and 25 
> in one set of experiments on telephony software".
> 
> Presumably this is with Erlang not with Haskell. I have 
> searched for the reference that substantiates this claim but 
> I've only been able to find:
> 
> http://set.gmd.de/~ap/femsys/wiger.html 
> 
> which talks about a productivity factor of 4
> 
> and
> 
> http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haske
ll-vs-ada-abstract.html

which suggests that Haskell is about 2-3 times as productive as imperative
languages.

Can someone point me at some more references? Especially the one that talks
about a productivity improvement of 9-25?

Thanks, Dominic.


-
21st century air travel http://www.britishairways.com

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Haskell Productivity

2000-12-20 Thread Peter Douglass

Hello all,
  You will need to manually reconnect the link I sent into a single line
for it to work.

> There is a thread on comp.lang.functional which may be of interest.
> Here is a link that might work for you.
> 
>
http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh
8ss$6le$[EMAIL PROTECTED]%3e%231/1
 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



GHC for Darwin?

2000-12-20 Thread Ashley Yakeley

Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant 
that runs on the PowerPC processor.
.

I was going to compile it myself before I remembered that compilers do 
platform-specific code-generation. Duh.

-- 
Ashley Yakeley, Seattle WA


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ANNOUNCE: Happy version 1.9

2000-12-20 Thread Simon Marlow

ANNOUNCING  Happy 1.9  - The LALR(1) Parser Generator for Haskell
-

I'm pleased to announce version 1.9 of Happy, the parser generator
system for Haskell.  Changes in this version, relative to version 1.8
(the previous full release):

* A grammar may now contain several entry points, allowing
  several parsers to share parts of the grammar.

* Some bugfixes.

Happy is available in source form, which can be compiled with GHC
version 4.xx (4.08.1 recommended), and we also provide binaries for
some architectures.  The Happy homepage with links to the various
distributions lives at:

http://www.haskell.org/happy/

Please send any bug reports and comments to [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell