Re: [Haskell-cafe] OCaml list sees abysmal Language Shootout results

2004-10-06 Thread Ketil Malde
Greg Buchholz [EMAIL PROTECTED] writes:

 I've been looking at the other shootout results (with the hope of
 learning something about making haskell programs faster/less memory
 hungry) and I couldn't quite figure out why the Hashes, part II test
 comsumes so much memory ( http://shootout.alioth.debian.org/bench/hash2/ ). 
 So I started to try heap profiling, and generated the following graphs
 for the different types of profiles...

 biography = http://sleepingsquirrel.org/haskell/hash2_b.ps
 retainer  = http://sleepingsquirrel.org/haskell/hash2_r.ps
 closure   = http://sleepingsquirrel.org/haskell/hash2_d.ps
 type  = http://sleepingsquirrel.org/haskell/hash2_y.ps
 cost cntr = http://sleepingsquirrel.org/haskell/hash2_c.ps

 ...but I have a hard time figuring out how to prevent something like
 stg_ap_3_upd_info or void cells from consuming so much memory.

One thing you could do, is to move the pure definitions (constants and
functions) out of the monad.  This will make them separate cost
centres, with their own profile information.  I toyed with this, but
admittedly, it didn't change much in this case.  I think it is better
style, though.

A simple way to improve speed marginally, is to specify Int instead of
letting things default to Integer.  A more complex way, saving about
60% of the time, is to use unboxed arrays instead of strings for the
keys - memory consumption seems to be the same, though. 

To get memory consumption down, I tried a strict update function:

   update k fm = let x = (get hash1 k + get fm k) 
 in x `seq` addToFM fm k x

which slowed the program down(!), but reduced memory consumption from
about 25Mb to 1.5Mb.  So it seems that the memory consumption is due
to unevaluated values in the FMs.

BTW, I looked at the shootout web pages, but I couldn't find the
specification for any of the benchmarks.  What is and isn't allowed? 

-kzm


import System (getArgs) 
import Data.FiniteMap 
import Data.Array.Unboxed
import Maybe

type Key = UArray Int Char
type Map = FiniteMap (UArray Int Char) Int

hash1, hash2 :: Map
hash1 = listToFM $ zip keys [0..] 
hash2 = listToFM $ zip keys (repeat 0) 

keys :: [Key]
keys = map (\x - listArray (1,4+length (show x)) (foo_ ++ show x)) [0..] 
get :: Map - Key - Int
get fm k = fromJust $ lookupFM fm k 

update :: Key - Map - Map
update k fm = let x = (get hash1 k + get fm k) in x `seq` addToFM fm k x

foo_1 = keys!!1
foo_ = keys!!

main = do 
 [n] - getArgs  
 let res = foldr update hash2 (concat $ replicate (read n) keys) 
 putStrLn $ unwords $ map show [get hash1 foo_1,
get hash1 foo_, 
get res foo_1, 
get res foo_] 

-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OCaml list sees abysmal Language Shootout results

2004-10-06 Thread Ketil Malde
Ketil Malde [EMAIL PROTECTED] writes:

 To get memory consumption down, I tried a strict update function:

update k fm = let x = (get hash1 k + get fm k) 
  in x `seq` addToFM fm k x

 which slowed the program down(!), 

I wonder if this isn't due to never evaluating the values for
foo_2 to foo_9998 because of laziness?

 BTW, I looked at the shootout web pages, but I couldn't find the
 specification for any of the benchmarks.  What is and isn't allowed? 

For instance, changing the order of of the updates shaves another
10-20% off the time (because of cache-friendliness, I suppose):

  - let res = foldr update hash2 (concat $ replicate (read n) keys)
  + let res = foldr update hash2 (concat $ map (replicate (read n)) keys)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: What Functions are Standard?

2004-10-06 Thread John Goerzen
On 2004-10-06, Glynn Clements [EMAIL PROTECTED] wrote:
 I can't comment on nhc98, but the Haskell98 standard doesn't include
 any mechanism for binary I/O.

Ouch.  That seems like a major oversight to me.  Will there be any
effort to fix that in the future?

-- John


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


[Haskell-cafe] Re: How do I get a long iteration to run in constant space

2004-10-06 Thread W M

I take it that the extra case always fails but forces
the arguments to be evaluated?  Nice trick.

Thanks!
--wgm

--- [EMAIL PROTECTED] wrote:

 
 I added two lines to your code:
 
 iterate2 f x n | seq f $ seq x $ seq n $ False =
 undefined
 iterate2 f x n = --- as before
 
 rk4Next f h (x, y) | seq f $ seq h $ seq x $ seq y $
 False = undefined
 rk4Next f h (x, y) = -- as before
 
 I also increased ten times the number of steps for
 the last iteration,
 to make the example more illustrative.
putStr (show (rk4 stiff 0 1 (exp (-1)) 100))
 
 The rest of the code is unchanged. The program now
 runs on GHCi
 
 *Foo main
 Begin
 (1.0007,-6.503275017254139)
 (0.9062,-6.497717470015538)
 (1.0007918,-6.497716616653335)
 
 
 on on hugs
 
 Begin
 (1.0,-6.50327501725414)
 (0.906,-6.49771747001554)
 (1.000792,-6.49771661665334)
 
 with the default stack size for both interpreters.
 It seems the code
 does run in constant space now.
 
 The added lines are meant to turn the relevant
 functions from lazy to
 strict. When you see something like '(n-1)' and 'y +
 a1/6', it is a
 red flag. These are exactly the kinds of expressions
 that lead to
 memory exhaustion. Perhaps it is because the size of
 an unevaluated
 thunk for (n-1) is so much bigger than the size of
 the evaluated
 thunk. It seems that arithmetic expressions are the
 best candidates
 for some opportunistic evaluation...
 




__
Do you Yahoo!?
Yahoo! Mail - Helps protect you from nasty viruses.
http://promotions.yahoo.com/new_mail
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: What Functions are Standard?

2004-10-06 Thread Glynn Clements

Malcolm Wallace wrote:

   I can't comment on nhc98, but the Haskell98 standard doesn't include
   any mechanism for binary I/O.
  
  Ouch.  That seems like a major oversight to me.  Will there be any
  effort to fix that in the future?
 
 Note that, on Unix-like systems, there is no difference between
 text I/O and binary I/O on files.  It is only Windows that requires
 a separation of the modes.

There are two issues here.

The first is EOL conversion; as Malcom notes, this isn't an issue on
Unix, but it is an issue on Windows. On Windows, there is no standard
way to obtain the contents of a file such that \n and \r\n are
distinct.

The second is character encoding/decoding. The Haskell98 I/O functions
all deal with Chars. When reading a file, the byte stream is converted
to a list of characters using an *unspecified* encoding. AFAIK, all
implementations are currently hardcoded to assume ISO-8859-1, so you
can reliably obtain the original list of bytes using the ord function.

However, nothing in the standard dictates that ISO-8859-1 is used, and
there has been talk of using the locale's encoding instead. If that
were to happen, it would be practically (as well as theoretically)
impossible to perform binary I/O using the Haskell98 API, even on
Unix.

This issue has been beaten to death fairly recently, so I'm not going
to repeat it here. See the thread entitled Writing binary files from
Sep 11-18 for the details.

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


[Haskell-cafe] Re: OCaml list sees abysmal Language Shootout results

2004-10-06 Thread Andre Pang
On 29/09/2004, at 8:41 AM, Graham Klyne wrote:
I can see that this requires the original file to be kept for 3-time 
scanning,  so enough memory for the entire file will be required.  Is 
that *the* problem to which you allude?  I can't see any other problem 
here.  And why would this put Haskell at a disadvantage?
I've been watching this thread with interest, and posted my own 
thoughts on this thread and Haskell's performance in general as a blog 
entry.  Rather than repeat it all here, I'll post a link to it:

  http://www.algorithm.com.au/mt/haskell/haskells_performance.html
The executive summary of my thoughts is that it seems to be entirely 
possible to optimise Haskell to be competitive with other, more 
performance-focused languages, but it's hard, and you have to be a 
Haskell expert to do so.  One possible solution may be to allow for 
some extra, syntactically integrated declarations to be inserted by the 
programmer which enables much better optimisation (e.g. see how to 
write unboxed strict array example in Clean: much more clear and less 
work than using IOUArrays).  Performance is the one major reason I 
recommend many existing C programmers try out O'Caml rather than 
Haskell as their first functional programming language, and it would be 
really nice if optimisation was made a bit easier.

--
% Andre Pang : trust.in.love.to.save
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootout results

2004-10-06 Thread Tomasz Zielonka
On Wed, Oct 06, 2004 at 01:23:56PM -0400, Andre Pang wrote:
 I've been watching this thread with interest, and posted my own 
 thoughts on this thread and Haskell's performance in general as a blog 
 entry.  Rather than repeat it all here, I'll post a link to it:
 
   http://www.algorithm.com.au/mt/haskell/haskells_performance.html

I feel a bit guilty for my ugly wc implementation. At the moment of
writing the first version I was thinking only about efficiency, not
about elegance.

I shouldn't have use unsafeRead, because it doesn't give such a big
advantage here if you take the danger into account.

Secondly, my solution fails to separate file iteration from the algoritm
for the problem. We have already created on this list a version which is
fast and quite elegant at the same time, and I feel this one is better
for the shootout even if it's slower than the one currently used (but it
doesn't use unsafeRead). The good news is that the development GHC 6.3
compiles this to code which is almost as fast as the ugly one.

Maybe we should vote: which wc implementation should go to the shootout?

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Integrating Haskell into a J2EE environment

2004-10-06 Thread Paul Hudak
Ok, I understand.  I don't know much at all about J2EE, in fact!  I 
would just hate to see an interesting project be abandoned if all that 
is needed is a simple way to invoke the Haskell code with a string 
argument, say.  Perhaps Shoeb can tell us more about what he needs.

  -Paul
Doug Kirk wrote:
Yes, I agree, and didn't mean to write off Haskell (at which, I'm 
completely a newbie, trying to learn, and thankful for your book!).

However, I'm a Java pro, and there are many technical issues on the Java 
side that scream at me to keep out of the native arena, especially in a 
J2EE container environment, where funny things can happen with hot 
reloads (dumping old ClassLoaders for new ones), clustering, and the like.

So it wasn't out of denigration of Haskell that I made my 
recommendation; far from it...from what I've seen Haskell is perfect for 
implementing DSL's. Rather, from the Java side is where it becomes 
problematic. There have been many problems integrating with native 
libraries from within a J2EE container, and I try to seek the most 
cost-effective way (I'm an independent consultant) to get the problem 
solved for my customers.

--doug
On Oct 6, 2004, at 2:59 PM, Paul Hudak wrote:
I wouldn't write off Haskell so quickly.  All of what Shoeb describes 
concerning DSL issues might be much more easily solved in Haskell, and 
will certainly be more flexible than a hard-wired approach.  The J2EE 
interface might be ugly, but if the functionality needed is not too 
great it might not be too bad.  Generally speaking, these kinds of apps 
-- in this case a DSL for high-level business rules -- sounds like 
just the sort of thing that Haskell is good for.

  -Paul

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


Re: [Haskell-cafe] Integrating Haskell into a J2EE environment

2004-10-06 Thread Vincenzo Ciancia
On Tuesday 05 October 2004 23:33, Bhinderwala, Shoeb wrote:
 I came across a few papers that talk about writing a DSL with Haskell
 as the underlying support language. How is this done. Is it possible
 to create a sort of domain specific business scripting language
 easily. How does that then compile to Haskell code. And how can the
 Haskell code be invoked from Java.

You usually write a DSL in haskell as a library, using monads or arrows 
if it is the case, and exploiting monads and arrows syntax facilities. 
Names in libraries represent operations of the DSL, and do not (of 
course) necessarily compute results, but can do many things, including 
generating source code for another language - you can find a lot of 
information on the web, e.g.

http://www.cs.uu.nl/~daan/download/papers/dsec.ps
http://homepages.cwi.nl/~arie/papers/dslbib/

One of the most known examples is FRAN (or the more up-to-date Yampa), 
but there actually are a lot of applications from very different 
domains.

bye

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


[Haskell-cafe] 500 great lines of Haskell code?

2004-10-06 Thread Isaac Jones
This might be an interesting way to highlight the beauty and brevity
of Haskell.  Has anyone written a great 500-line Haskell program they
want to submit?

peace,

  isaac


http://developers.slashdot.org/article.pl?sid=04/10/06/1530218tid=156tid=8

Be part of the Open Source Annual 2005 and enter our hacker contest
for the best 500-line open source program. The best program will be
printed in next year's issue of the book. Following lasts year's huge
success with our Open Source Annual, a mostly German reader concerned
with the various aspects of open source, we are currently busy
compiling the second edition of the annual which will be released next
March for the CeBIT 2005 in Hannover. Aside from articles on subjects
like economics, law and open innovation, to name but a few, we plan to
print the source code of an open source software program.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe