Re: [Haskell-cafe] Re: Shootout favoring imperative code

2006-01-12 Thread Bulat Ziganshin
Hello Einar,

Wednesday, January 11, 2006, 6:06:56 PM, you wrote:

 My version of the packed string library does have an hGetLine.  Don
 Stewart was merging my version with his fps at some point, Don - any 
 news on that?

EK Getting a fast FastPackedString will solve the problems with many
EK benchmarks.

btw, JHC's version of FPS uses slightly less memory (i don't remember,
8 or 12 bytes per each string) and i think must be faster (because it
uses ByteArray# instead of Addr#). so, the best variant is to add hGetLine
to John's library

   set arr x yv

(arr,x) =: yv

looks better ;)

EK and so forth. Usually imperative solutions have something like
EK a[i] += b[i], which currently is quite tedious and ugly to
EK translate to MArrays. Now it would become combineTo a i (+) b i.

you are definitely a Hal Daume's client, look at 
http://www.isi.edu/~hdaume/STPP/


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-11 Thread Einar Karttunen
On 09.01 11:32, Simon Marlow wrote:
 Sebastian Sylvan wrote:
 
 It would be neat if the PackedString library contained functions such
 as hGetLine etc. It does have a function for reading from a buffer,
 but it won't stop at a newline...
 But yeah, fast string manipulation is difficult when using a
 linked-list representation...
 
 My version of the packed string library does have an hGetLine.  Don 
 Stewart was merging my version with his fps at some point, Don - any 
 news on that?

Getting a fast FastPackedString will solve the problems with many
benchmarks. A similar thing for arrays would be nice - although
this is more about inteface:

 module Data.Array.UnsafeOps where

 import Data.Array.Base hiding((!))

 {-# INLINE (!) #-}
 (!) :: MArray a e m = a Int e - Int - m e
 (!) = unsafeRead

 {-# INLINE set #-}
 set :: MArray a e m = a Int e - Int - e - m ()
 set = unsafeWrite

 {-# INLINE swap #-}
 swap :: MArray a e m = a Int e - Int - Int - m ()
 swap arr x y = do xv - arr ! x
   yv - arr ! y
   set arr x yv
   set arr y xv

 {-# INLINE combineTo #-}
 combineTo :: MArray a e m = a Int e - Int - (e - e - e) - a Int e - 
 Int - m ()
 combineTo a0 i0 f a1 i1 = do v0 - a0 ! i0
  v1 - a1 ! i1
  set a0 i0 $! f v0 v1

and so forth. Usually imperative solutions have something like
a[i] += b[i], which currently is quite tedious and ugly to
translate to MArrays. Now it would become combineTo a i (+) b i.

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


[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-09 Thread Simon Marlow

Sebastian Sylvan wrote:


It would be neat if the PackedString library contained functions such
as hGetLine etc. It does have a function for reading from a buffer,
but it won't stop at a newline...
But yeah, fast string manipulation is difficult when using a
linked-list representation...


My version of the packed string library does have an hGetLine.  Don 
Stewart was merging my version with his fps at some point, Don - any 
news on that?


Cheers,
Simon

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


[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-06 Thread Chris Kuklewicz
[EMAIL PROTECTED] wrote:
There is no need to beat a dead horse, though.  This benchmark sets out
to test fgets / atoi, and that is all.  There are better benchmarks to
spend time on.
 
 
 You can say that again!
 
Ah..sarcasm, I know that one.

Actually, I submitted a slightly faster sum-file entry for Haskell
tonight.  So I did kick the horse around, and I learned how to use
-funbox-strict-fields.

 Is a persecution complex required for Haskell programming :-)

The sum-file benchmark is not about my cleverness.  It is designed to
test the language's library routines.  I quote Brent:

 Yes -- it was designed as a test of the standard I/O
 system.
 
 -Brent

See...It is like the startup benchmark -- which just tests how long it
takes to start the program (and print Hello World.).

 
 ackermann, sum-file, random, startup (aka hello world) are all
 left-over from the old Doug Bagley Great Computer Language Shootout -
 they are just little snippets of nothing that provide an easy starting
 point - takfp and harmonic are much the same.

takfp and ackerman and harmonic can be good tests of how well the
langauage handles recursion.

 
 I'm waiting for the complaints that binary-trees was designed to favour
 functional programming languages ;-)

;-) == sarcasm

 
 best wishes, Isaac
 
Cheers,
  Chris


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


[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-06 Thread Isaac Gouy
I sent a private email and the response to it has
appeared on this mailing-list, so let me just correct
some of the interpretations that have been made.

  You can say that again!

 Ah..sarcasm, I know that one.

No, it was emphatic agreement (the ordinary usage of
that phrase).


  Is a persecution complex required for Haskell 
  programming :-)

This one is sarcasm. Hi Sebastian :-)


  I'm waiting for the complaints that binary-trees
was designed
  to favour functional programming languages ;-)

 ;-) == sarcasm

Actually no - binary-trees was written with functional
programming languages very much in mind.

best wishes, Isaac



__ 
Yahoo! DSL – Something to write home about. 
Just $16.99/mo. or less. 
dsl.yahoo.com 

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