Re: [Haskell-cafe] Parsing words with parsec

2007-03-30 Thread Paolino

On 3/30/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Fri, Mar 30, 2007 at 05:43:34AM +0200, paolino wrote:
 Hi,
 I had a bad time trying to parse the words of a text.
 I suspect I miss some parsec knowledge.

I'd start by not sextuple-posting, it just sextuples the ugliness ;-)

Mhh, still I don't see any them in my inbox mails , probably something
buggy in gmail configuration, sorry :/.



import Char( isAlpha )
import List( groupBy )

equating f x y = f x == f y  -- in Data.Eq, iff you have GHC 6.7

isLetter x = isAlpha x || x == '_' || x == '@'

myWords = filter (isLetter . head) . groupBy (equating isLetter)



Testing your code, it misses the words with numbers inside exclusion
and uses the number as separators.

!runhaskell prova.hs
[[EMAIL PROTECTED],sara,mimmo,ab,a,b,ab,cd]

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


RE: [Haskell-cafe] sending from Gmail (was Parsing words with parsec)

2007-03-30 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Paolino
 
  I'd start by not sextuple-posting, it just sextuples the 
 ugliness ;-)
 Mhh, still I don't see any them in my inbox mails , probably something
 buggy in gmail configuration, sorry :/.

Are you expecting to see your sent message eventually arrive in your
inbox? gmail doesn't do that by default (and I don't see an obvious
setting to change it). gmail seems to be fairly keen on removing
duplicate messages.

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
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sending from Gmail (was Parsing words with parsec)

2007-03-30 Thread Paolo Veronelli
On Friday 30 March 2007 11:44, Bayley, Alistair wrote:
  From: [EMAIL PROTECTED]
  [mailto:[EMAIL PROTECTED] On Behalf Of Paolino
 
   I'd start by not sextuple-posting, it just sextuples the
 
  ugliness ;-)
  Mhh, still I don't see any them in my inbox mails , probably something
  buggy in gmail configuration, sorry :/.

 Are you expecting to see your sent message eventually arrive in your
 inbox? gmail doesn't do that by default (and I don't see an obvious
 setting to change it). gmail seems to be fairly keen on removing
 duplicate messages.

Then probably I was expecting haskell-cafe to send messages sent by me to me 
also so I can have my messages in the thread automatically. Or , I have to 
copy them from the sent box to the haskell-cafe filter box ?
I'm confused.

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


Re: [Haskell-cafe] sending from Gmail (was Parsing words with parsec)

2007-03-30 Thread Dougal Stanton

On 30/03/07, Bayley, Alistair [EMAIL PROTECTED] wrote:


 Mhh, still I don't see any them in my inbox mails , probably something
 buggy in gmail configuration, sorry :/.

Are you expecting to see your sent message eventually arrive in your
inbox? gmail doesn't do that by default (and I don't see an obvious
setting to change it). gmail seems to be fairly keen on removing
duplicate messages.


The ML software has the option of not sending you your own messages,
but I can't remember if it is on by default or not.

Cheers,

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


Re: [Haskell-cafe] sending from Gmail (was Parsing words with parsec)

2007-03-30 Thread Paolo Veronelli
On Friday 30 March 2007 11:54, Dougal Stanton wrote:
 On 30/03/07, Bayley, Alistair [EMAIL PROTECTED] 
wrote:
   Mhh, still I don't see any them in my inbox mails , probably something
   buggy in gmail configuration, sorry :/.
 
  Are you expecting to see your sent message eventually arrive in your
  inbox? gmail doesn't do that by default (and I don't see an obvious
  setting to change it). gmail seems to be fairly keen on removing
  duplicate messages.

 The ML software has the option of not sending you your own messages,
 but I can't remember if it is on by default or not.

Just controlled , it's set to Yes on receiving copy of my posts. Thanks 
anyway.

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


Re: [Haskell-cafe] Monad/Functor Book

2007-03-30 Thread jim burton


Dave-86 wrote:
 
 Given the amount of material posted at haskell.org and elsewhere
 explaining IO, monads and functors, has anyone considered publishing
 a comprehensive book explaining those subjects?  (I am trying to
 read all the material online, but books are easier to read and don't
 require sitting in front of a computer to do so. Plus I can write in
 books :-). )
 
 Thanks, Dave Feustel
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
Print out the wikibook [1]? IMO it has good coverage of Monads, more
detailed than any of the textbooks I've read, and leads into CT and advanced
topics that aren't really covered in any of the books (partly because a  lot
of it isn't Haskell 98 of course).

[1] http://en.wikibooks.org/wiki/Haskell 
-- 
View this message in context: 
http://www.nabble.com/Monad-Functor-Book-tf3474082.html#a9752877
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Compiling GHC

2007-03-30 Thread Ian Lynagh
On Fri, Mar 30, 2007 at 04:36:32PM +1000, Chris Witte wrote:
 I'm tying to compile GHC under mingw (winxp with mingw no cygwin),
 
 Loading package base ... linking ... ghc.exe: unable to load package `base'
 ghc.exe:
 C:/msys/1.0/local/HSbase.o: unknown symbol `_gettimeofday'
 
 
 any ideas on what could be causing this.

What does

grep -i gettimeofday mk/config.h

say?

If HAVE_GETTIMEOFDAY is defined then either comment it out (between
running configure and running make), or work out why the configure test
is succeeding but it doesn't work when GHC tries to use it.


Thanks
Ian

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


[Haskell-cafe] Data.ByteStream.Char8.words performance

2007-03-30 Thread Dino Morelli

I noticed something about ByteStream performance that I don't
understand.

I have a test text document:

   $ ls -sh test-text-file
   956K test-text-file


Running this program, using the Prelude's IO functions:


module Main where

main = do
   content - readFile test-text-file
   let l = length . words $ content
   print l


I get:

   $ time ./a.out
   174372

   real0m0.805s
   user0m0.720s
   sys 0m0.008s


Running a version of the same thing using Data.ByteStream.Char8:


module Main where

import qualified Data.ByteString.Char8 as B

main = do
   content - B.readFile test-text-file
   let l = length . B.words $ content
   print l


I see a time that is quite a bit slower:

   $ time ./a.out
   174372

   real0m1.864s
   user0m1.596s
   sys 0m0.012s


Changing it to incorporate similar code to the implementation of
B.words:


module Main where

import qualified Data.ByteString.Char8 as B
import Data.Char (isSpace)

main = do
   content - B.readFile test-text-file
   let l = length $ filter (not . B.null) $ B.splitWith isSpace
   content
   print l


I see a similar time as with B.words:

   $ time ./a.out
   174372

   real0m1.835s
   user0m1.628s
   sys 0m0.012s


And then if I change this to use B.split ' ' instead of isSpace:


module Main where

import qualified Data.ByteString.Char8 as B

main = do
   content - B.readFile test-text-file
   let l = length $ filter (not . B.null) $ B.split ' ' content
   print l


I get a time that's much more reasonable-looking, compared to the
original Prelude.words version:

   $ time ./a.out
   174313

   real0m0.389s
   user0m0.312s
   sys 0m0.004s


It seems like the B.splitWith isSpace code is really slow for some
reason. Anybody have any idea what's going on? The actual implementation
is using isSpaceWord8 which is a case statement looking for a pile of
different whitespace characters.


--
 .~.Dino Morelli
 /V\email: [EMAIL PROTECTED]
/( )\   irc: dino-
^^-^^   preferred distro: Debian GNU/Linux  http://www.debian.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.ByteStream.Char8.words performance

2007-03-30 Thread Jeremy Shaw
Hello,

Did you compile with -O2 ? That makes a huge difference when using ByteString.

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


Re: [Haskell-cafe] Lambdabot not running on XP

2007-03-30 Thread Iain Alexander
On 29 Mar 2007 at 15:18, Stefan O'Rear wrote:

 On Thu, Mar 29, 2007 at 08:29:51PM +0100, Iain Alexander wrote:
[snip]
  (ghc-6.4.1, lambdabot-4.0, WinXP SP2)
 
 As a result of my recentish code cleanups, everything lambdabot does,
 even the main command loop, is a @-command.  If you just run it as
 'lambdabot', you give it zero commands, so it loads all plugins,
 executes zero commands, and quits.  I suppose I could make the command
 loop the default, but that is just too ugly since as it stands the
 core doesn't know the command loop even exists.  You want 'lambdabot
 -e offline' or 'lambdabot -e rc online.rc'.  Note that none of this
 applies if you are using the tarball. 

Usage: lambdabot [--online|--restricted]

(As I said, I'm using lambdabot-4.0)
-- 
Iain Alexander  [EMAIL PROTECTED]


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


Re: [Haskell-cafe] Data.ByteStream.Char8.words performance

2007-03-30 Thread Dino Morelli

On Fri, 30 Mar 2007, Jeremy Shaw wrote:


Hello,

Did you compile with -O2 ? That makes a huge difference when using ByteString.

j.



Ah, that was exactly it. I feel silly.



module Main where

import qualified Data.ByteString.Char8 as B

main = do
   content - B.readFile test-text-file
   let l = length . B.words $ content
   print l



$ ghc -O2 count-b.hs
$ time ./a.out
174372

real0m0.198s
user0m0.136s
sys 0m0.012s


Much faster. Thank you!


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


Re: [Haskell-cafe] Data.ByteStream.Char8.words performance

2007-03-30 Thread Duncan Coutts
On Fri, 2007-03-30 at 14:24 -0700, Jeremy Shaw wrote:
 Hello,
 
 Did you compile with -O2 ? That makes a huge difference when using ByteString.

Hmm, I think we can do better than that. It would be nicer to have it
work fast without needing any -O flags at all in the user's module.

Lets look at the current def again:

words :: ByteString - [ByteString]
words = P.filter (not . B.null) . B.splitWith isSpaceWord8
{-# INLINE words #-}

So this will always inline words into your program (when using -O or
-O2) however there is nothing really to be gained from doing that.
There's no fusion going on here, it's always going to (lazily) allocate
the result list.

So I think it's probably better to just remove the inline pragma. In
fact Dino's original program might work faster with -O0 than -O1. :-)

The best you could do with the current definition (rather than writing a
specialised implementation) is something like:

words = P.filter (not . B.null) . words'
{-# INLINE words #-}

words' = B.splitWith isSpaceWord8
{-# NOINLINE words' #-}

since the filter could fuse in the calling context with a good list
consumer but the B.splitWith is not a good producer in it's current
definition so there is no benefit to inlining it. All that gives you is
the potential to compile it badly in the calling module rather than just
calling the single compiled version in the ByteString lib (that was of
course built with -O2).

The ByteString libs was more-or-less the first high performance thing
that we wrote and we've learnt plenty more since then. I think there's a
good deal more performance too eek out of it yet, both at the low and
high level.

Duncan

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