On 17-Sep-1999, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
> Mark Engelberg wrote:
>
> >
> > This is a huge difference, and makes Haskell look incredibly slow by
> > comparison. The speed difference in this case is well worth the extra few
> > lines of code.
>
> Well, Hugs is an interpreter. Comparing interpreted Haskell with compiled
> C++ isn't really fair. Try compiling yout program with a Haskell compiler,
> e.g. hbc or ghc.
Well, I tried with ghc 2.08 -- admittedly an ancient version, so
this is not a fair comparison, but that was what I had on hand.
On a 300 MHz DEC Alpha system, I got the following times:
Language Compiler version Options Time
Haskell ghc 2.08 -O 21.5 seconds
Mercury rotd-1999-09-17 -O6 7.5 seconds
Mercury rotd-1999-09-17 -O6 --gc none 2.2 seconds
C++ egcs-1.1.2 -O3 .2 seconds
Hmm... a ratio of about 100:10:1 for Haskell:Mercury:C++ is, well,
interesting ;-).
I wonder how much better ghc 4.x does?
Cheers,
Fergus.
P.S.
Here's my Mercury code.
:- module solve_it.
:- interface.
:- import_module io.
:- pred main(io__state::di, io__state::uo) is cc_multi.
:- implementation.
:- import_module list, int.
main --> (if { answer(Answer) } then print(Answer) else print("no")), nl.
expand(A,B,C,D,E,F) = F + E*10 + D*100 + C*1000 + B*10000 + A*100000.
answer(Answer) :-
permute([0,1,2,3,4,5,6,7,8,9], Answer),
Answer = [T,H,I,R,Y,W,E,L,V,N],
expand(T,H,I,R,T,Y) + 5 * expand(T,W,E,L,V,E) = expand(N,I,N,E,T,Y).
permute([], []).
permute([X|Y], [U|V]) :- del(U, [X|Y], Z), permute(Z, V).
del(A, [A|L], L).
del(X, [A|Z], [A|R]) :- del(X, Z, R).
--
Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.