RE: [Haskell-cafe] Rethinking OO idioms

2004-09-30 Thread Bayley, Alistair
There are three pieces to this story:
 - read a config file into some structure
 - query/modify elements of that structure
 - write structure out to a file

Create a data structure (analogous to a class with no methods) and functions
to query/manipulate that structure. Nested FiniteMaps might be a good,
simple, first attempt. Unlike the functions to read and write the file
(which must be in the IO monad), the functions to query and manipulate the
structure can (and probably should) be non-monadic.

Ben suggested using Parsec for reading the config file. Parsec is a fine
library, but there is a learning curve, and you might find it quicker to do
the parsing yourself, if it's very simple. Your call.

> ... Haskell has no mutable variables.  A call like
> config.setOption("main", "initpath", "/usr") in Python -- which alters
> the state of the config object and returns nothing -- would be
> impossible in Haskell (unless perhaps the FiniteMaps are mutable
> somehow?)

When you "modify" a structure, you return a new copy of it, where the bit
that you wanted to change is replaced by the new value. For example, this is
what happens when you call addToFM/delFromFM for FiniteMaps. This isn't
necessarily as expensive as it sounds, as there's a lot of data sharing
going on in Haskell programs, due to the fact that everything /is/
immutable.

If it does turn out to be too expensive, then you could look at using a
state monad. But assuming you need one immediately looks like premature
optimisation to me.

Alistair.

-
*
Confidentiality Note: The information contained in this 
message, and any attachments, may contain confidential 
and/or privileged material. It is intended solely for the 
person(s) or entity to which it is addressed. Any review, 
retransmission, dissemination, or taking of any action in 
reliance upon this information by persons or entities other 
than the intended recipient(s) is prohibited. If you received
this in error, please contact the sender and delete the 
material from any computer.
*

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


Re: [Haskell-cafe] Rethinking OO idioms

2004-09-30 Thread David Roundy
On Wed, Sep 29, 2004 at 08:29:47PM +, John Goerzen wrote:
> So I am thinking about a ConfigParser for Haskell.  The first thing that
> occured to me is that Haskell has no OO features, so I'm not sure what
> is the best way to handle the "class" and its various methods.
> 
> The next thing that occured to me is that, unlike OCaml and Python
> classes, Haskell has no mutable variables.  A call like
> config.setOption("main", "initpath", "/usr") in Python -- which alters
> the state of the config object and returns nothing -- would be
> impossible in Haskell (unless perhaps the FiniteMaps are mutable
> somehow?)

I might define just two IO functions:

parseConfig :: FilePath -> IO Config
modifyConfig :: FilePath -> (Config -> Config) -> IO Config

This way, you could do all the modification in pure functional code, which as
Alastair said, would create a "new" Config rather than modifying the
existing one.

Of course, you could also define a

writeConfig :: FilePath -> Config -> IO ()

but then a user of your class could accidentally overwrite a change, if you
had two parts of the code which read the same config, each made separate
changes, and then each wrote their separate changes.
-- 
David Roundy
http://www.abridgegame.org
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Seeking reference(s) relating to FP performance

2004-09-30 Thread Graham Klyne
Thanks... it's interesting to see that functional languages in general, and 
especially ML derivatives, do show comparable performance to languages like 
Python, Perl and Java.

But what I was really after was an indication of trends.  The impression I 
have is that longer the term trend is to close gap between FPLs and (say) 
C, and it is for that I'd like some supporting evidence, or indications.

#g
--
At 19:00 29/09/04 +, John Goerzen wrote:
On 2004-09-29, Graham Klyne <[EMAIL PROTECTED]> wrote:
> I've taken it as an article of faith that performance of FP language
> implementations has been improving quite steadily over the past few
> years.  I'd like to assert this, but I can't find any clear evidence to
One place to start is the Language Shootout at
http://shootout.alioth.debian.org/.  While it is a benchmark, and
therefore subject to all sorts of standard disclaimers about rigged
benchmarks, some interesting conclusions can be seen:
1. OCaml often performs better than g++
2. OCaml sometimes even beats gcc.
3. ghc doesn't seem to do very well in terms of performance, though it
does at least beat out Java in many cases.
4. ghc has some of the most concise programs out there
There's not a lot of information there on historical trends, but the
fact that a mostly-functional language like OCaml can beat out c++ is
fairly impressive.
-- John
> I'm looking for a reference -- informal will be enough -- that can give an
> perspective of progress in functional language implementation
> performance.  I'm not looking for a single benchmark that shows a case of
> blindingly-fast functional code, but a pointer to trends of improving
> performance.  It would also serve my purpose to have indications based on
> languages other than Haskell (e.g. ML and friends).
>
> Any ideas, please?
>
> #g
>
>
> 
> Graham Klyne
> For email:
> http://www.ninebynine.org/#Contact
--
John Goerzen
Author, Foundations of Python Network Programming
http://www.amazon.com/exec/obidos/tg/detail/-/1590593715
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Rethinking OO idioms

2004-09-30 Thread Graham Klyne
At 01:44 30/09/04 +, John Goerzen wrote:
On 2004-09-29, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
> You can use state monad to mimic mutation.
Is that really what I want?  In other words, is there a completely
different, more Haskellish, way to look at this?
> Also, take a look at the recursive decent monadic parsec library. It may
> have done what you are trying to do.
Thanks for the pointer.  I'll take a look.
Sometimes what you want really *is* a mutable value of some kind, but far 
less than you might expect.

I recently implemented an RDF/XML parser using Parsec to parse from an 
"event stream" of XMLish things.  Parsec is Monadic, and provides for user 
state in the parser, which I duly used.  But the amount of user state I 
used was tiny:

[[
data RDFParserState = RDFParserState
{ nodegen   :: Int
, listgen   :: Int
}
]]
I.e., just two counters that were used for generating identifiers within 
the parsing process.  Everything else was quite comfortably treated as 
immutable values.

The code can be seen at:
  http://www.ninebynine.org/Software/HaskellRDF/RDF/Harp/RDFXMLParser.hs
The function that invokes Parsec being 'parseEventsToRDF'.  (This may not 
be the best introductory example, because it touches a lot of other 
logic.  There is a test suite in the same directory if you want to dig deeper.)

#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Simple example using Parsec (was: [Haskell-cafe] Rethinking OO idioms)

2004-09-30 Thread Graham Klyne
At 09:01 30/09/04 +0100, Bayley, Alistair wrote:
Ben suggested using Parsec for reading the config file. Parsec is a fine
library, but there is a learning curve, and you might find it quicker to do
the parsing yourself, if it's very simple. Your call.
Hmmm... Parsec *can* be simple too.  Here's one I did earlier:
  http://www.ninebynine.org/Software/HaskellUtils/RegexParser.hs
#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
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-09-30 Thread Malcolm Wallace
Just out of interest, I ran all of these suggested variations of
the word count solution in Haskell head-to-head against each other.
Here are the results, in seconds, on my machine (2.4GHz x86/Linux)
for the suggested input (N=500) from the shootout site.  All Haskell
versions were compiled with ghc-5.04.2 -O2.

original space-leaky2.257
Greg Buchholz   1.619   *
Sam Mason   0.594
Malcolm Wallace 0.457
Georg Martius   0.322   *
Tomasz Zielonka 0.047
linux 'wc'  0.085

Those marked with a * gave the wrong number of words.  The really
interesting thing is that Tomasz's solution is twice as fast as the
standard Gnu implementation!

Regards,
Malcolm
___
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-09-30 Thread Tomasz Zielonka
On Thu, Sep 30, 2004 at 11:26:15AM +0100, Malcolm Wallace wrote:
> Those marked with a * gave the wrong number of words.  The really
> interesting thing is that Tomasz's solution is twice as fast as the
> standard Gnu implementation!

That's probably because Gnu wc is locale aware.

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: Simple example using Parsec (was: [Haskell-cafe] Rethinking O O idioms)

2004-09-30 Thread Bayley, Alistair
Sure. Learning Parsec took me a few hours, whereas John's parsing task might
be done in much less time, if it's simple enough. OTOH, there's value in
being able to use Parsec, so it's a good excuse to learn.


> -Original Message-
> From: Graham Klyne [mailto:[EMAIL PROTECTED] 
> Sent: 30 September 2004 10:34
> To: Bayley, Alistair; 'John Goerzen'; [EMAIL PROTECTED]
> Subject: Simple example using Parsec (was: [Haskell-cafe] 
> Rethinking OO idioms)
> 
> At 09:01 30/09/04 +0100, Bayley, Alistair wrote:
> >Ben suggested using Parsec for reading the config file. 
> Parsec is a fine
> >library, but there is a learning curve, and you might find 
> it quicker to do
> >the parsing yourself, if it's very simple. Your call.
> 
> Hmmm... Parsec *can* be simple too.  Here's one I did earlier:
>http://www.ninebynine.org/Software/HaskellUtils/RegexParser.hs
> 
> #g

-
*
Confidentiality Note: The information contained in this 
message, and any attachments, may contain confidential 
and/or privileged material. It is intended solely for the 
person(s) or entity to which it is addressed. Any review, 
retransmission, dissemination, or taking of any action in 
reliance upon this information by persons or entities other 
than the intended recipient(s) is prohibited. If you received
this in error, please contact the sender and delete the 
material from any computer.
*

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


[Haskell-cafe] Re: Compiling GHC for AIX5.1L

2004-09-30 Thread John Goerzen
On 2004-09-30, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> You can use make -k to keep going, I seem to remember, or use -pgmltrue,

Those tricks got me farther.  Now I'm on the target and stuck at:

gmake[5]: Entering directory
`/home/jgoerzen/programs/unreg/ghc-6.2.1/ghc/rts/gm
p/mpn'
m4 -DPIC -DOPERATION_mul_1 mul_1.asm >tmp-mul_1.s
/bin/sh ../libtool --mode=compile gcc -c -DHAVE_CONFIG_H -I. -I. -I..
-I.. -DOPE
RATION_mul_1-g -O2 tmp-mul_1.s -o mul_1.lo
gcc -c -DHAVE_CONFIG_H -I. -I. -I.. -I.. -DOPERATION_mul_1 -g -O2
tmp-mul_1.s -o
 mul_1.o
 tmp-mul_1.s: Assembler messages:
 tmp-mul_1.s:55: Error: Unrecognized opcode: `mulhwu'
 tmp-mul_1.s:61: Error: Unrecognized opcode: `mulhwu'
 tmp-mul_1.s:67: Error: Unrecognized opcode: `mulhwu'
 tmp-mul_1.s:73: Error: Unrecognized opcode: `mulhwu'
 tmp-mul_1.s:82: Error: Unrecognized opcode: `mulhwu'
 tmp-mul_1.s:91: Error: Unrecognized opcode: `mulhwu'
 gmake[5]: *** [mul_1.lo] Error 1
 gmake[5]: Leaving directory
 `/home/jgoerzen/programs/unreg/ghc-6.2.1/ghc/rts/gmp
 /mpn'


> to have ghc skip the linking phase. This was a common trick when we went
> through a porting frenzy last year. Check the mailing list archives for
> lots of hints.
>
>http://www.haskell.org/pipermail/glasgow-haskell-users/2003-September/thread.html
>
> Adding something like:
>  AR=/usr/bin/true
>  LD=/usr/bin/true
>  SRC_HC_OPTS+= -pgmc /usr/bin/true -pgma /usr/bin/true -pgml /usr/bin/true
> to build.mk might help.
>
> Good luck! :)
>
> -- Don
>
>> ==fptools== make all -r;
>>  in /home/jgoerzen/no-backup/programs/ghc-6.2.1/ghc/rts
>>  
>>  ../../ghc/compiler/ghc-inplace -optc-O -optc-Wall -optc-W
>>  -optc-Wstrict-prototypes -optc-Wmissing-prototypes
>>  -optc-Wmissing-declarations -optc-Winline -optc-Waggregate-return
>>  -optc-Wbad-function-cast -optc-I../includes -optc-I. -optc-Iparallel
>>  -optc-DCOMPILING_RTS -optc-fomit-frame-pointer -H16m -O -O2 -static
>>  -c Adjustor.c -o Adjustor.o
>>  /tmp/ghc10917.s: Assembler messages:
>>  /tmp/ghc10917.s:54: Error: no such instruction: `dcbf 0,%eax'
>>  /tmp/ghc10917.s:55: Error: no such instruction: `sync'
>>  /tmp/ghc10917.s:56: Error: no such instruction: `icbi 0,%eax'
>>  /tmp/ghc10917.s:63: Error: no such instruction: `sync'
>>  /tmp/ghc10917.s:64: Error: no such instruction: `isync'
>>  make[1]: *** [Adjustor.o] Error 1
>>  make: *** [all] Error 1
>> 
>> Why it's trying to use PowerPC assembler on an x86 host I don't know.
>> (I assume that's what's going on here; but I don't really know.)


-- 
John Goerzen
Author, Foundations of Python Network Programming
http://www.amazon.com/exec/obidos/tg/detail/-/1590593715

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


Re: [Haskell-cafe] Rethinking OO idioms

2004-09-30 Thread Jeremy Jones
John (and Haskell community),
I just subscribed to the Haskell mailing list the other day and this 
posting grabbed my attention.  I've been workin with Python for a few 
years now and have recently decided to try to expand my horizons to 
Haskell (and OCaml).  I love Python, but I feel like I could learn a lot 
that could be applied to Python from understanding FP languages like 
Haskell (and OCaml).  That being said, can you point me to any 
documentation online or books that are more suited to a Python person 
trying to understand Haskell (and OCaml)?  Any help is appreciated.

Jeremy Jones

John Goerzen wrote:
I've worked with languages with object-oriented features for awhile now.
Python and OCaml, the two with which I work the most, both have OO.
One of my first projects in Haskell would be to write a Haskell version
of Python's ConfigParser[1] class.  I wrote[2],[3] a version of this for
OCaml that works very well.
In a nutshell, ConfigParser is a utility for working with sectioned
configuration files in a style similar to the familiar .ini files from
Windows.  It has methods to read a configuration file, get/set the items
that are being configured, and write a new file back out.  This, then,
is a fairly typical metaphor for OO programs: an instance of a class has
some state that can be accessed or modified, and possibly stored and
retrieved.
So I am thinking about a ConfigParser for Haskell.  The first thing that
occured to me is that Haskell has no OO features, so I'm not sure what
is the best way to handle the "class" and its various methods.
The next thing that occured to me is that, unlike OCaml and Python
classes, Haskell has no mutable variables.  A call like
config.setOption("main", "initpath", "/usr") in Python -- which alters
the state of the config object and returns nothing -- would be
impossible in Haskell (unless perhaps the FiniteMaps are mutable
somehow?)  

I guess I'm having trouble translating this common OO language paradigm
into the Haskell world.
Thanks for any insight.
-- John
BTW, if I get a working ConfigParser for Haskell, I will publish it
under the GPL like all the rest of my code.
[1] http://www.python.org/doc/current/lib/RawConfigParser-objects.html
[2] http://gopher.quux.org:70/devel/missinglib/html/ConfigParser.html
[3] http://gopher.quux.org:70/devel/missinglib/html/ConfigParser.rawConfigParser.html
___
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: [Haskell-cafe] Rethinking OO idioms

2004-09-30 Thread John Goerzen
On Thursday 30 September 2004 07:54 am, Jeremy Jones wrote:
> John (and Haskell community),
>
> I just subscribed to the Haskell mailing list the other day and this
> posting grabbed my attention.  I've been workin with Python for a few
> years now and have recently decided to try to expand my horizons to
> Haskell (and OCaml).  I love Python, but I feel like I could learn a
> lot that could be applied to Python from understanding FP languages
> like Haskell (and OCaml).  That being said, can you point me to any

One of the interesting things about Python is that it has slowly been 
adding functional programming mechanisms to the language.  Some of the 
constructs we all love in FP are available on Python.  For instance:

 * anonymous functions ("lambda" keyword)

 * nested scopes and the ability to return functions

 * iterable objects

On the other hand, Python's typing system is nowhere near as powerful as 
that of Haskell or OCaml.  OCaml, and to an even larger extent, 
Haskell, have a wonderful typing system: it's strong, yet it 
inobtrusive.  I am a fan of that, and it helps these languages scale to 
large projects better than Python -- while at the same time keeping 
them suitable for small ones (unlike, say, Java)

OCaml has an object system.  It's not as powerful as Python's in most 
respects, and can be loosely described as a functional hybrid of the 
Python and Java object systems 

I find myself writing most of my new code in OCaml these days.  If I can 
manage to get a Haskell compiler built on AIX, I may move to 
Haskell :-)

(Building anything on that platform is difficult, sigh)

> documentation online or books that are more suited to a Python person
> trying to understand Haskell (and OCaml)?  Any help is appreciated.

This is a great resource:  Learning OCaml for C, C++, Perl, and Java 
programmers:

http://www.merjis.com/developers/ocaml_tutorial/

I wish something like that existed for Haskell.  I may write one 
someday. :-)

Once you know OCaml, though, Haskell will come a lot easier.  The typing 
systems are quite similar, as are many of the concepts.  I/O is very 
different though.  Haskell I/O is different from anything else I've 
ever seen, so I can't really come up with a good analogy for you 
there :-)

This is a good Haskell tutorial: http://www.isi.edu/~hdaume/htut/
___
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-09-30 Thread Kevin Everets
On Thu, Sep 30, 2004 at 11:26:15AM +0100, Malcolm Wallace wrote:

> Just out of interest, I ran all of these suggested variations of
> the word count solution in Haskell head-to-head against each other.
> Here are the results, in seconds, on my machine (2.4GHz x86/Linux)
> for the suggested input (N=500) from the shootout site.  All Haskell
> versions were compiled with ghc-5.04.2 -O2.
> 
>   original space-leaky2.257
>   Greg Buchholz   1.619   *
>   Sam Mason   0.594
>   Malcolm Wallace 0.457
>   Georg Martius   0.322   *
>   Tomasz Zielonka 0.047
>   linux 'wc'  0.085
> 
> Those marked with a * gave the wrong number of words.  The really
> interesting thing is that Tomasz's solution is twice as fast as the
> standard Gnu implementation!

I took Georg's, fixed the word count logic and added prettier
printing, and then combined it with Sam's main (which I find more
elegant, but others may find less straightforward).  I think it
strikes a good balance between efficiency and elegance.

Cheers,

Kevin.

--

import IO

main = getContents >>= putStrLn . showC . foldl wc' (C 0 0 0 False)

data C = C !Int !Int !Int !Bool deriving Show
-- Line Word Char InWord

showC (C l w c _) = show l ++ " " ++ show w ++ " " ++ show c

wc' :: C  -> Char -> C
wc' (C l w c _) '\n' = C (l+1) w (c+1) False
wc' (C l w c _) ' '  = C l w (c+1) False
wc' (C l w c _) '\t' = C l w (c+1) False
wc' (C l w c False) _= C l (w+1) (c+1) True
wc' (C l w c True)  _= C l w (c+1) True
___
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-09-30 Thread Tomasz Zielonka
On Thu, Sep 30, 2004 at 09:49:46AM -0400, Kevin Everets wrote:
> I took Georg's, fixed the word count logic and added prettier
> printing, and then combined it with Sam's main (which I find more
> elegant, but others may find less straightforward).  I think it
> strikes a good balance between efficiency and elegance.

Then how about a solution like this: I took your program but used
my fast fileIterate instead of ,,foldl over getContents''. 
I also added {-# OPTIONS -funbox-strict-fields #-}, and played a bit
to get the best optimisations from GHC.

It's about 7 times faster this way, but it's still two times slower than
the solution I sent to shootout.

Devilish plan: Maybe we could have some variants of fileIterate in GHC's
libraries? ;->

I remember that someone proposed similar functions on haskell's lists
some time ago, but can't remember who.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links

{-# OPTIONS -funbox-strict-fields #-}

import System.IO
import Data.Array.IO
import Data.Array.Base
import Data.Word
import Data.Int
import List
import Char

main = fileIterate stdin wc' (C 0 0 0 False) >>= putStrLn . showC

data C = C !Int !Int !Int !Bool deriving Show
-- Line Word Char InWord

showC (C l w c _) = show l ++ " " ++ show w ++ " " ++ show c

wc' :: C  -> Char -> C
wc' (C l w c _) '\n' = C (l+1) w (c+1) False
wc' (C l w c _) ' '  = C l w (c+1) False
wc' (C l w c _) '\t' = C l w (c+1) False
wc' (C l w c False) _= C l (w+1) (c+1) True
wc' (C l w c True)  _= C l w (c+1) True



{-# INLINE fileIterate #-}

fileIterate :: Handle -> (a -> Char -> a) -> a -> IO a
fileIterate h f a0 = do
buf <- newArray_ (0, bufSize - 1) :: IO (IOUArray Int Word8)
let loop i n a
| i `seq` n `seq` a `seq` False = undefined
| i == n =
do  n' <- hGetArray h buf bufSize
if n' == 0
then return a
else loop 0 n' a
| otherwise =
do  c <- fmap (toEnum . fromEnum) (readArray buf i)
loop (i + 1) n (f a c)
loop 0 0 a0
  where
bufSize :: Int
bufSize = 4096

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


[Haskell-cafe] State monad strictness (was: ... abysmal Language Shootout results)

2004-09-30 Thread Peter Simons
How can anyone stay away from such a deliciously pointless
waste of time as implementing a wc(1) derivate? :-)

Here is my attempt:

 > import IO
 >
 > type Count = Int
 > data CountingState = ST !Bool !Count !Count !Count
 >  deriving (Show)
 >
 > initCST = ST True 0 0 0
 >
 > wc :: CountingState -> [Char] -> CountingState
 > wc (ST _ l w c) ('\n':xs) = wc (ST True (l+1)  w   (c+1)) xs
 > wc (ST _ l w c) (' ' :xs) = wc (ST True   lw   (c+1)) xs
 > wc (ST _ l w c) ('\t':xs) = wc (ST True   lw   (c+1)) xs
 > wc (ST True  l w c) ( x  :xs) = wc (ST False  l  (w+1) (c+1)) xs
 > wc (ST False l w c) ( x  :xs) = wc (ST False  lw   (c+1)) xs
 > wc st [] = st
 >
 > main :: IO ()
 > main = do
 >   ST _ l w c <- getContents >>= return . wc initCST
 >   putStrLn $ (l `shows`) . spaces . (w `shows`) . spaces . (c `shows`) $ []
 > where spaces = (' ':) . (' ':) . (' ':)

I compiled this with "ghc -O2 -funbox-strict-fields" and got
the following performance results in a simple test.

The wc(1) tool:

$ time /usr/bin/wc  import IO
 > import Control.Monad.State
 >
 > type Count = Int
 > data CountingState = ST !Bool !Count !Count !Count
 >  deriving (Show)
 >
 > type WordCounter   = State CountingState ()
 >
 > initCST = ST True 0 0 0
 >
 > wc :: Char -> WordCounter
 > wc x = get >>= \(ST b l w c) ->
 >   case (b,x) of
 > (  _  , '\n') -> put (ST True (l+1) w (c+1))
 > (  _  , '\t') -> put (ST True   l   w (c+1))
 > (  _  , ' ' ) -> put (ST True   l   w (c+1))
 > (True,   _  ) -> put (ST False  l  (w+1) (c+1))
 > (False,  _  ) -> put (ST False  lw   (c+1))
 >
 > main :: IO ()
 > main = do
 >   xs <- getContents
 >   let ST _ l w c = snd (runState (mapM wc xs) initCST)
 >   putStrLn $ (l `shows`) . spaces . (w `shows`) . spaces . (c `shows`) $ []
 > where
 > spaces = (' ':) . (' ':) . (' ':)

Curiously enough, this version fails to process the "words"
file because it runs out of stack space! Naturally, it is
very slow, too. So I wonder: How needs that program above to
be changed in order to solve this space leak?

Why does this happen in the first place?

Peter

___
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-09-30 Thread Greg Buchholz
Sam Mason wrote:
> 
> You probably want some strictness annotations in there. . .

Now we're getting somewhere.  When I replace the tuples with my own
(strict) data structure, it gets about 7.5 times faster than the original
shootout example (or about 24 times faster than the version with
tuples).  I get another 2x speedup when I pass '+RTS -G1' to the
executable.  So the version below is about 15 times faster than the
original using the 3MB data file from the shootout. (Now we're only
about 40x slower than ocaml).  Don't forget to turn on '-funbox-strict-fields' 
for an additional improvement.

-- Compile with...
-- ghc -O2 -ddump-simpl -fvia-c -funbox-strict-fields -o wc_fold2 wc_fold2.hs
-- execute as...  ./wc_fold2 +RTS -G1 http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-09-30 Thread Graham Klyne
At 16:56 30/09/04 +0200, Tomasz Zielonka wrote:
Then how about a solution like this: I took your program but used
my fast fileIterate instead of ,,foldl over getContents''.
I also added {-# OPTIONS -funbox-strict-fields #-}, and played a bit
to get the best optimisations from GHC.
It's about 7 times faster this way, but it's still two times slower than
the solution I sent to shootout.
Devilish plan: Maybe we could have some variants of fileIterate in GHC's
libraries? ;->
Two responses:
1. I agree that providing the right kind of library functions (and material 
explaining how to use them) maybe a key to getting efficient code without 
losing high-level forms of expression.

2. Your fileIterator certainly looks nicer (to me) than your other 
solution, but...

Tagging along with this debate, I found myself wondering if, in order to 
get performance comparable to other languages, it is really necessary to 
write code like code in other languages.  E.g., I thought one of the 
lessons of John Hughes' "Why functional Programming matters" was that one 
can achieve greater efficiencies by climbing higher rather than dropping 
down to the level of other languages.  Your fileIterate looks to me like a 
step in the right direction.

But I did wonder if it wouldn't be possible to also abstract out the I/O 
element of your 'fileIterate', using instead something like:
  streamIterate :: [b] -> (a -> b -> a) -> a -> IO a

(I was originally thinking of something like:
  streamIterate :: (c -> (b,c)) -> c -> (a -> b -> a) -> a -> IO a
where the first argument is a function that takes a sequence generator and 
returns the next member of the sequence+new generator, and the 2nd arg is 
the initial generator.)

For such an approach to be useful, I think it would also be important to 
have variations of functions like length, lines, words that can be combined 
to make a function like your wc'.

#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
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-09-30 Thread Tomasz Zielonka
On Thu, Sep 30, 2004 at 05:40:58PM +0100, Graham Klyne wrote:
> 2. Your fileIterator certainly looks nicer (to me) than your other 
> solution, but...

It looks nicer to me too.

> Tagging along with this debate, I found myself wondering if, in order to 
> get performance comparable to other languages, it is really necessary to 
> write code like code in other languages.

Maybe it's not necessary to get the comparable performance, but it often
is if you want to get the best performance possible. Of course I
wouldn't mind if GHC optimised high level code so well, that we wouldn't
have to do it, but I guess it's just not that easy. 

What I like about GHC is that I can start from simple, high-level,
sometimes slow solutions, but if there are efficiency problems, there is
a big chance that I can solve them without switching the language.

> But I did wonder if it wouldn't be possible to also abstract out the I/O 
> element of your 'fileIterate', using instead something like:
>   streamIterate :: [b] -> (a -> b -> a) -> a -> IO a

It seems to be a variant of foldl. You can eliminate IO from return
type, or is there some reason for it?

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] OCaml list sees abysmal Language Shootout results

2004-09-30 Thread Graham Klyne
At 19:39 30/09/04 +0200, Tomasz Zielonka wrote:
What I like about GHC is that I can start from simple, high-level,
sometimes slow solutions, but if there are efficiency problems, there is
a big chance that I can solve them without switching the language.
That's a very good point, I think.  One to hang on to.
> But I did wonder if it wouldn't be possible to also abstract out the I/O
> element of your 'fileIterate', using instead something like:
>   streamIterate :: [b] -> (a -> b -> a) -> a -> IO a
It seems to be a variant of foldl. You can eliminate IO from return
type, or is there some reason for it?
Doh!  (Why didn't I spot that?)  All roads lead to Rome, or something like 
that?  There seems to be a recurring tension between how much to specialize 
and how much to generalize.

Maybe it should be something like:
  streamIterate :: (Monad m) => [b] -> (a -> b -> m a) -> a -> m a
?
Er, but that's similarly a variation of foldM, right?
Or maybe my earlier idea was closer:
  streamIterate :: (Monad m) =>
  (c -> m (b,c)) -> c -> (a -> b -> m a) -> a -> m a
?
Hmmm... I feel like a (intellectual) bull-in-a-china-shop here.  I'm 
blundering about on the trail of a delicate and elegant idea that I'm sure 
others could dissect far more clearly.

What I'm trying to capture (I think) is that there's some baggage to do 
with accessing the raw data and emitting the desired result that needs to 
be carried along (or interleaved) with the required computation on that 
data.  Does this make any sense, or am I descending into farce here?

#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
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-09-30 Thread Georg Martius
Hi folks,
On Thu, 30 Sep 2004 01:02:54 +0100, Sam Mason <[EMAIL PROTECTED]> wrote:
Greg Buchholz wrote:
The algorithm isn't correct (it counts spaces instead of words), but
anyone have advice for improving its performance?
You probably want some strictness annotations in there. . .

Last night as I have tried to improve Gregs wc in a simple fashion and came up with 
the same idea to make a new data type with strict fields. I thought why one couldn't 
add some kind of strictness annotation to the function type. First attempt:
wc :: !(Int,Int,Int) -> Char -> (Int, Int, Int)
As far as I know the compiler does strictness analysis to find strict arguments in a 
function anyway. Would it make sense to allow this kind of explicit strictness? Where 
are the problems with that?
I mean lazyness is really useful and it is our best friend in this kind of 
application, since we can make stream processing without implementing a buffer and so 
on. On the other hand one gets occasionally traped by it and it is not allways easy to 
grasp why.
Some more general comment: The code for the shootout doesn't need to be extremly fast 
in my eyes, it needs to be elegant and reasonable at performance and memory 
consuptions (In this order). I don't want to say that Thomaszs solution is bad, but it 
is not a typical Haskell style application. If someone (not haskeller) looks at the 
implementation it should be very obvious and clear.
The last few weeks the list have been full of performance questions (including my own 
ones) and it is really a pitty that it is such an issue. I believe that most problems 
occuring with performance and memory consumptions could be easily solved by partial 
and explicit strictness. Please enlight me if I am wrong.
Regards,
 Georg
___
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-09-30 Thread Greg Buchholz
Malcolm Wallace wrote:
> Here are the results, in seconds, on my machine (2.4GHz x86/Linux)
> for the suggested input (N=500) from the shootout site.  All Haskell
> versions were compiled with ghc-5.04.2 -O2.

I thought I'd take a stab at timing a few of the examples with
different compiler versions to see what difference that would make
(ghc-6.2.1 vs. ghc-6.3.20040928).  I compared Kevin Everets' version with
the two Tomasz Zielonka versions.  I ran the test with N=2500 (i.e. 2500
copies of the original file, which is what is apparently used in the
shootout) on my AthlonXP 1600 under x86/Linux.

6.2.1   6.3.20040928
--- ---
Kevin   3.615s  3.156s  
Kevin  (+RTS -G1)   1.666s  1.405s
Tomasz (pretty) 0.725s  0.481s
Tomasz (fast)   0.403s  0.430s

Interesting to see the speed increase going from 6.2.1 to 6.3 for
Tomasz' pretty example.  Anyone have an explaination for the 2x speed
increase for running Kevin's version with '+RTS -G1'?

(And for reference, here's the results on my machine for the perl and
gcc versions of the test and gnu/wc)

perl-5.8.4  0.535s
gcc-3.4.2   0.102s
gnu/wc  0.435s

Greg Buchholz

___
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-09-30 Thread Andrew Cheadle
Hi Greg

>Anyone have an explaination for the 2x speed
>increase for running Kevin's version with '+RTS -G1'?

+RTS -Sstderr -RTS and +RTS -sstderr -RTS will probably indicate why.
I'd be surprised if the amount of data copied for the semi-space
collector isn't much less than for the generational.

Chances are that data is dying off very quickly and very little is
being copied for the semi-space collector - the allocation area
has a variable sizing policy and this size of allocation area is
sufficient for the majority of the data to die off before it is filled
and a GC kicks in - hence very little is copied. However, for the
generational collector, the nursery is of fixed size. Here, the lifetime
of the data is probably longer than the time it takes for the nursery to
be filled and a minor GC kicks in and the data promoted to generation 1
(hence copied) where it then probably dies off but can't be collected
until a major collection kicks in.

Probably, or something like that ;-)

Cheers

Andy

*
*  Andrew Cheadleemail:  [EMAIL PROTECTED] *
*  Department of Computing   http://www.doc.ic.ac.uk/~amc4/ *
*  Imperial College *
*  University of London *
*
___
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-09-30 Thread Greg Buchholz
Andrew Cheadle wrote:
> 
> +RTS -Sstderr -RTS and +RTS -sstderr -RTS will probably indicate why.
> I'd be surprised if the amount of data copied for the semi-space
> collector isn't much less than for the generational.

Ahh. Data copied with '-G1' = 58MB vs. 203MB without.  For posterities 
sake, here are the numbers...

With '-G1'
---
306,616,872 bytes allocated in the heap
 58,844,344 bytes copied during GC
 99,316 bytes maximum residency (1169 sample(s))

   1169 collections in generation 0 (  0.62s)

  1 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.68s  (  0.71s elapsed)
  GCtime0.62s  (  0.68s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time1.30s  (  1.39s elapsed)

  %GC time  47.7%  (48.9% elapsed)

  Alloc rate450,907,164 bytes per MUT second

  Productivity  52.3% of total user, 48.9% of total elapsed


Without
---
306,616,872 bytes allocated in the heap
203,339,812 bytes copied during GC
109,088 bytes maximum residency (131 sample(s))

   1169 collections in generation 0 (  2.22s)
131 collections in generation 1 (  0.05s)

  2 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.79s  (  0.92s elapsed)
  GCtime2.27s  (  2.23s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time3.06s  (  3.15s elapsed)

  %GC time  74.2%  (70.8% elapsed)

  Alloc rate388,122,622 bytes per MUT second

  Productivity  25.8% of total user, 25.1% of total elapsed


Greg Buchholz
___
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-09-30 Thread Greg Buchholz
Georg Martius wrote:
> Some more general comment: The code for the shootout doesn't need to be 
> extremly fast in my eyes, it needs to be elegant and reasonable at 
> performance and memory consuptions (In this order). I don't want to say 
> that Thomaszs solution is bad, but it is not a typical Haskell style 
> application. If someone (not haskeller) looks at the implementation it 
> should be very obvious and clear.

It might also be nice if the code would run under the other haskell
compliers like Hugs and nhc98 right out-of-the-box.


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


Re: [Haskell-cafe] Re: Compiling GHC for AIX5.1L

2004-09-30 Thread Donald Bruce Stewart
jgoerzen:
> On 2004-09-30, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> > You can use make -k to keep going, I seem to remember, or use -pgmltrue,
> 
> Those tricks got me farther.  Now I'm on the target and stuck at:
> 
> gmake[5]: Entering directory
> `/home/jgoerzen/programs/unreg/ghc-6.2.1/ghc/rts/gm
> p/mpn'
> m4 -DPIC -DOPERATION_mul_1 mul_1.asm >tmp-mul_1.s
> /bin/sh ../libtool --mode=compile gcc -c -DHAVE_CONFIG_H -I. -I. -I..
> -I.. -DOPE
> RATION_mul_1-g -O2 tmp-mul_1.s -o mul_1.lo
> gcc -c -DHAVE_CONFIG_H -I. -I. -I.. -I.. -DOPERATION_mul_1 -g -O2
> tmp-mul_1.s -o
>  mul_1.o
>  tmp-mul_1.s: Assembler messages:
>  tmp-mul_1.s:55: Error: Unrecognized opcode: `mulhwu'
>  tmp-mul_1.s:61: Error: Unrecognized opcode: `mulhwu'
>  tmp-mul_1.s:67: Error: Unrecognized opcode: `mulhwu'
>  tmp-mul_1.s:73: Error: Unrecognized opcode: `mulhwu'
>  tmp-mul_1.s:82: Error: Unrecognized opcode: `mulhwu'
>  tmp-mul_1.s:91: Error: Unrecognized opcode: `mulhwu'
>  gmake[5]: *** [mul_1.lo] Error 1
>  gmake[5]: Leaving directory
>  `/home/jgoerzen/programs/unreg/ghc-6.2.1/ghc/rts/gmp
>  /mpn'

It could be that gmp is a bit too old for your platform. This has been
the case on other rarer platforms, and on (all?) 64bit archs. One
solution is to install a native, newer libgmp yourself (from the
vendor), and then add appropriate flags to have ./configure and gcc/ghc
find the library (if it isn't in a standard location).

On Irix I needed:
export LDFLAGS="-L/usr/freeware/lib64"
export CPPFLAGS="-I/usr/freeware/include"

cat >> mk/build.mk 

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

2004-09-30 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes:

>> wc :: !(Int,Int,Int) -> Char -> (Int, Int, Int)

> I'm not sure if that was your question

Sorry about that, brain malfunction, bangs are for data declarations,
I'll get that cup of coffee now. 

I guess what you really want to do, is to put some `seq`s in there.
Something like: 

wc (cs,ws,ls) ... = cs `seq` ws `seq` ls `seq` ...the def. of wc...

which evaluates the Ints before doing anything else.  Or use (!$)
(like function application ($), but strict).

-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