Re: can a lazy language give fast code?

2002-07-29 Thread Andrew J Bromage

G'day all.

On Mon, Jul 29, 2002 at 10:23:05AM +0100, Simon Marlow wrote:

> Many of those programs can be written differently to improve
> performance.

To be fair, Doug admits this as well as a lot more:

http://www.bagley.org/~doug/shootout/method.shtml#flaws

Despite these flaws, I did notice that ghc is right in the middle in
his CRAPS score system (which is really interesting; all due respect
to the GHC guys, but I expected it to be lower ).

I also noticed that the majority of cases where Haskell does
significantly worse than average are "same way" tests, designed to test
the performance of various constructs (e.g. array access, dictionary
lookup) as opposed to "same thing" tests, designed to test native
idioms.

In the end, though, benchmarks ignore one of the most important rules
of software performance: "throughput" (i.e. the amount of processing
that your system can do just prior to being overloaded) is almost never
the most important consideration.  Other considerations such as
flexibility, robustness, responsiveness and scalability are almost
always more important.

I've thought for a while that what we need is more benchmarks like
pseudoknot: Real tasks which real people want to do.  Computing
Ackermann's function is all well and good, but when's the last time you
actually needed to compute it in a real program?

Off the top of my head, some "real" tasks which could be benchmarked
include:

- MPEG video compression.

- Code scheduling/register allocation for a CPU like the
  MIPS/Alpha or even the IA64.

- Fluid simulation.

- Solving chess problems.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: can a lazy language give fast code?

2002-07-29 Thread Scott J.

What I also meant but did not write was this: is there anyone who would like
to redo these benchmarks and see what it gives with all the new inventions
the DHC supports?

Cheers

Scott


- Original Message -
From: "Simon Marlow" <[EMAIL PROTECTED]>
To: "Scott J." <[EMAIL PROTECTED]>; <[EMAIL PROTECTED]>
Sent: Monday, July 29, 2002 11:23 AM
Subject: RE: can a lazy language give fast code?


> > Can one write withthe Haskell compliler faster code than in
> > the examples of http://www.bagley.org/~doug/shootout/  where
> > GHC (old Haskell 98?) seems to be much slower than Ocaml  or
> > Mlton both strict functional languages.
> > Can one expect any improvements in speed in the future?
>
> Many of those programs can be written differently to improve
> performance.  One issue that is affecting performance in several cases
> is the speed of character I/O, and the representation of Strings as
> lists of characters.  Dramatic improvements can be had by using unboxed
> arrays of Char (Data.Array.Unboxed), or PackedString (which these days
> is implemented using unboxed arrays in GHC).
>
> Cheers,
> Simon
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

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



Re: Infix expressions

2002-07-29 Thread Jon Fairbairn

Ken Shan <[EMAIL PROTECTED]> wrote:
> In Haskell, backquotes can be used to convert individual identifiers
> into infix operators, but not complex expressions.  For example,
> 
> [1,2,3] `zip` [4,5,6]
> 
> is OK, but not
> 
> [1,2,3] `zipWith (+)` [4,5,6]
> 
> Is there any reason other than potential confusion when one of the two
> backquotes is accidentally omitted?

I've often wondered about this myself, but it's difficult to
make a pleasant distinction between what's allowed in
between `` and an ordinary expression. They can't be the
same because you can't nest them. Using a matched pair of
quotation marks would work, but then you have the
possibility of writing really horrid expressions.

> In any case, perhaps some people on this mailing list would appreciate
> the following implementation of "infix expressions" that Dylan Thurston
> and I came up with -- as algebraic and perverse as we could manage:
> 
> infixr 0 -:, :-
> data Infix f y = f :- y
> x -:f:- y = x `f` y
> 
> main = print $ [1,2,3] -: zipWith (+) :- [4,5,6]

Yes, I appreciate that! It reminds me of how I got the
syntax of Ponder -- which had no predefined operators, not
even "if" -- to work.

> The trick is that there is no trick.

Oh, I think it /is/ a trick :-)

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


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



Re: Infix expressions

2002-07-29 Thread Hal Daume III

> Is there any reason other than potential confusion when one of the two
> backquotes is accidentally omitted?

I thought about this a while ago and I think it probably simply has to do
with complexity of expressions.  If you allow arbitrary expressions to
appear within the ticks, you have a problem with:

  x `f a `b` g c` y

does this mean

  (b (f a) (g c)) x y

or

  f a x (g c b y)

or what?

You could impose the constraint that you can't have embedded ticks, but
this would grossify the CFG.  Furthermore, you then have the case of, why
isn't this valid:

  a `f (x `g` y)` b

where the embedding is unambiguous because of the parentheses.  i don't
really know, but i find this fairly difficult to read.

  a `h` b where h = x `g` y

is a lot simpler imo...

 - Hal

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



Infix expressions

2002-07-29 Thread Ken Shan

Hello,

In Haskell, backquotes can be used to convert individual identifiers
into infix operators, but not complex expressions.  For example,

[1,2,3] `zip` [4,5,6]

is OK, but not

[1,2,3] `zipWith (+)` [4,5,6]

Is there any reason other than potential confusion when one of the two
backquotes is accidentally omitted?

In any case, perhaps some people on this mailing list would appreciate
the following implementation of "infix expressions" that Dylan Thurston
and I came up with -- as algebraic and perverse as we could manage:

infixr 0 -:, :-
data Infix f y = f :- y
x -:f:- y = x `f` y

main = print $ [1,2,3] -: zipWith (+) :- [4,5,6]

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
The trick is that there is no trick.



msg01848/pgp0.pgp
Description: PGP signature


Haskell is more known than we might think

2002-07-29 Thread oleg


Hello!

The other day I received, among other junk mail, coupons for the local
7-eleven store. I subconsciously scanned the envelope, and almost
jumped when I read the return address:

7-Eleven, Inc.
2711 North Haskell Avenue
Dallas, TX 75204

It seems a rather long Avenue (with at least 27 blocks); presumably it
has the Southern part too. Being associated with the most successful
worldwide convenience store chain bodes well for the language.

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



RE: can a lazy language give fast code?

2002-07-29 Thread Simon Marlow

> Can one write withthe Haskell compliler faster code than in 
> the examples of http://www.bagley.org/~doug/shootout/  where 
> GHC (old Haskell 98?) seems to be much slower than Ocaml  or 
> Mlton both strict functional languages.
> Can one expect any improvements in speed in the future?

Many of those programs can be written differently to improve
performance.  One issue that is affecting performance in several cases
is the speed of character I/O, and the representation of Strings as
lists of characters.  Dramatic improvements can be had by using unboxed
arrays of Char (Data.Array.Unboxed), or PackedString (which these days
is implemented using unboxed arrays in GHC).

Cheers,
Simon 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe