Re: [Haskell-cafe] Parsing words with parsec

2007-03-31 Thread Paolo Veronelli
On Friday 30 March 2007 06:59, Stefan O'Rear wrote:

 Anyway, I think parsec is *far* too big a hammer for the nail you're trying
 to hit.

In the end , the big hammer solution has become

parseLine = fmap (map fst. filter snd) $ many parser 
  where parser = do w - option (,False) parseAWord  
anyChar -- skip the separator
return w
parseAWord = try positive | (many1 nonSeparator  return 
(,False)) 
positive = do c - wordChar
  (cs,tn) - option (,True) parseAWord
  return (c:cs,tn)
   
wordChar = letter | oneOf _@ ? a word-character
 
nonSeparator = wordChar | digit ? a non-separator

while your, corrected not parsec solution is

wordsOfLine isNonSeparator isWordChar = (filter (all isWordChar)).
 groupBy (\x y - (isNonSeparator x) == (isNonSeparator y)) 

Still ,I wonder if the parsec solution can be simplified.

Thanks.

(PS. I put an option on the ML software which sends me an ack on posting , so 
at least I know I sent the mail :) )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


[Haskell-cafe] Parsing words with parsec

2007-03-29 Thread paolino
Hi, 
I had a bad time trying to parse the words of a text.
I suspect I miss some parsec knowledge.

In the end it seems working, though I haven't tested much and this example 
contains the main features I was looking.

*Main parseTest (parseLine eof) [EMAIL PROTECTED] sara,mimmo! 9ab a9b ab9 
cd\n
[[EMAIL PROTECTED],sara,mimmo,cd]

-
manyTillT body terminator joiner = liftM2 joiner (manyTill body (lookAhead  
terminator)) terminator

wordChar = letter | oneOf _@ ? a valid word character

nonSeparator = wordChar | digit

wordEnd = do 
 x - wordChar
 notFollowedBy nonSeparator
 return x

word = manyTillT wordChar (try wordEnd) (\b t - b ++ [t]) ? a word

wordStart = do 
   (try nonSeparator  unexpected non separator) | anyChar
   lookAhead wordChar

nextWord =  manyTill anyChar (try wordStart)  (try word | nextWord)

parseLine end = do 
   f - option [] $ return `fmap` try word
   r - many $ try nextWord
   manyTill anyChar end
   return (f ++ r)   

---

Any comment to simplify this code is welcome.


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


[Haskell-cafe] Parsing words with parsec

2007-03-29 Thread paolino
Hi, 
I had a bad time trying to parse the words of a text.
I suspect I miss some parsec knowledge.

In the end it seems working, though I haven't tested much and this example 
contains the main features I was looking.

*Main parseTest (parseLine eof) [EMAIL PROTECTED] sara,mimmo! 9ab a9b ab9 
cd\n
[[EMAIL PROTECTED],sara,mimmo,cd]

-
manyTillT body terminator joiner = liftM2 joiner (manyTill body (lookAhead  
terminator)) terminator

wordChar = letter | oneOf _@ ? a valid word character

nonSeparator = wordChar | digit

wordEnd = do 
 x - wordChar
 notFollowedBy nonSeparator
 return x

word = manyTillT wordChar (try wordEnd) (\b t - b ++ [t]) ? a word

wordStart = do 
   (try nonSeparator  unexpected non separator) | anyChar
   lookAhead wordChar

nextWord =  manyTill anyChar (try wordStart)  (try word | nextWord)

parseLine end = do 
   f - option [] $ return `fmap` try word
   r - many $ try nextWord
   manyTill anyChar end
   return (f ++ r)   

---

Any comment to simplify this code is welcome.


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