Re: [Haskell-cafe] csv one-liner

2008-10-02 Thread Marco Túlio Gontijo e Silva
Op woensdag 01-10-2008 om 18:59 uur [tijdzone -0700], schreef Jason
Dusek:
> Reply to all?

No.  Reply-to-list is a different thing.  When you reply-to-all to a
person who is in the list, the person gets two copies of the e-mail with
different headers, which messes with filters and replies.

Greetings.

-- 
marcot
Página: http://marcotmarcot.iaaeee.org/
Blog: http://marcotmarcot.blogspot.com/
Correio: [EMAIL PROTECTED]
XMPP: [EMAIL PROTECTED]
IRC: [EMAIL PROTECTED]
Telefone: 25151920
Celular: 98116720
Endereço:
  Rua Turfa, 639/701
  Prado 30410-370
  Belo Horizonte/MG Brasil


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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Jason Dusek
  Reply to all?

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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Marco Túlio Gontijo e Silva
Op woensdag 01-10-2008 om 10:15 uur [tijdzone +0200], schreef Ketil
Malde:
> Derek Elkins <[EMAIL PROTECTED]> writes:
> 
> >> parseCSVFromFile "in.csv" >>= return . either (const "error!")
> 
> > Whenever you see this >>= return . f pattern think liftM or fmap or <$>.
> 
> ...and "return . f >>= action" is just "action . f", no?

Maybe you meant "return f >>= action" is the same as "action f".

Greetings.

-- 
marcot
Página: http://marcotmarcot.iaaeee.org/
Blog: http://marcotmarcot.blogspot.com/
Correio: [EMAIL PROTECTED]
XMPP: [EMAIL PROTECTED]
IRC: [EMAIL PROTECTED]
Telefone: 25151920
Celular: 98116720
Endereço:
  Rua Turfa, 639/701
  Prado 30410-370
  Belo Horizonte/MG Brasil


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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Marco Túlio Gontijo e Silva
Op woensdag 01-10-2008 om 13:25 uur [tijdzone -0700], schreef Martin
DeMello:
> 2008/10/1 wman <[EMAIL PROTECTED]>:
> >
> > PS: Sorry, Andrew, that I first posted the reply directly to you, still
> > getting used to the fact that gmail kindly replies to the user on whose
> > behalf the message was sent, not to the list.
> 
> I think that's a list setting, not a gmail one.

The list could set reply-to, which is usually not very recommended in
netiquettes.  And gmail doesn't have a reply-to-list option, which is
very useful when the lists doesn't set reply-to, like haskell-cafe.

Greetings.

-- 
marcot
Página: http://marcotmarcot.iaaeee.org/
Blog: http://marcotmarcot.blogspot.com/
Correio: [EMAIL PROTECTED]
XMPP: [EMAIL PROTECTED]
IRC: [EMAIL PROTECTED]
Telefone: 25151920
Celular: 98116720
Endereço:
  Rua Turfa, 639/701
  Prado 30410-370
  Belo Horizonte/MG Brasil


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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Claus Reinke

(writeFile "output.csv") =<< (liftM printCSV $ liftM (map
updateLine) $ parseCSVFromFile "input.csv")



Um... Does anybody else find it interesting that we are "showing the
beauty of Haskell" by attempting to construct the most terse, cryptic,
unmaintainable tangle of point-free code


I don't agree at all!  How could a pipeline like this possibly be more
clearly expressed than by the pattern: 


  readInputFile "input" >>= mungeStuff >>= writeOutputFile "output"


   interact pureMungeStuff

After all, you're looking for oneliners, not real programs.

   interact $ either (error . show) (printCSV . map updateLine) . parseCSV "" 


Claus

-- some people need a vacation


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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread wman
On Wed, Oct 1, 2008 at 10:40 PM, Andrew Coppin
<[EMAIL PROTECTED]>wrote:

> Maybe I should start a new tradition where Haskellers have a blob of
> Haskell as their sig?
>
> (I can't *wait* to see what the luminaries such as dons, dcoutts and igloo
> come up with...)
>

Some haskell equivalent of :

(lambda(x)x x)x)x)x)x)x)x)x))
(lambda(x)(lambda(y)(x(x y)
   (lambda(x)(x)x))
  (lambda()(printf "Greetings, Jos~n"

? ;-)))

and seeing ketil's sig, i cannot keep to myself this beautiful
bastardization of the "shoulders of giants" line which i found today:

Most men stand on the shoulders of giants. Matthew Garrett stamps on the
testicles of midgets.

PS: it seems the list won't re-send the message to people to whom it was
directly addressed. so to stay in my on-click lazy mode, i'm trying the
reply-to-all button. In the case i start flooding your mailboxes, just
kindly kick my butt. thx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Ketil Malde
Andrew Coppin <[EMAIL PROTECTED]> writes:

>> (writeFile "output.csv") =<< (liftM printCSV $ liftM (map
>> updateLine) $ parseCSVFromFile "input.csv")

> Um... Does anybody else find it interesting that we are "showing the
> beauty of Haskell" by attempting to construct the most terse, cryptic,
> unmaintainable tangle of point-free code

I don't agree at all!  How could a pipeline like this possibly be more
clearly expressed than by the pattern: 

   readInputFile "input" >>= mungeStuff >>= writeOutputFile "output"

?  The OP asks for improvements, which got rid of a couple of
gratuitous liftMs and such, but otherwise I think it's a pretty
straightforward idiom.

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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Andrew Coppin

wman wrote:

Thats why i put those quotation marks around that part of sequence ;-))
AFAIK one-liners never were about comprehensibility, just about what 
you can cram into one line of code.


Any programmer should have no problems guessing what the line does 
does (even more so when looking at the "final" version without the 
abundant liftM's), the beauty of it lies in figuring how the heck it 
does what it does. And figuring that out should bring the "profound 
enlightenment experience; that experience which should make you a 
better programmer for the rest of your days, even if you never 
actually use Lisp -erm Haskell- itself a lot" (my apologies, P. 
Graham, for cannibalizing your words).


I should probably get myself a signature stating that i will 
explicitly warn the reader when being serious ;-)


Ah, well then... ;-)

Over in the land of POV-Ray, it's sort-of a tradition for your email 
signature to contain a tiny block of Scene Description Language source 
code that causes POV-Ray to render your name, or at least render 
something appropriate. (For those who don't know, POV-Ray is a ray 
tracer who's Scene Description Language is now in fact Turing-complete - 
although it is only a sort of macro expansion kind of beast.)


Maybe I should start a new tradition where Haskellers have a blob of 
Haskell as their sig?


(I can't *wait* to see what the luminaries such as dons, dcoutts and 
igloo come up with...)


Ah, but a blob of code that does _what_? POV-Ray renders your name in 
trippy 3D, but Haskell...?


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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Martin DeMello
2008/10/1 wman <[EMAIL PROTECTED]>:
>
> PS: Sorry, Andrew, that I first posted the reply directly to you, still
> getting used to the fact that gmail kindly replies to the user on whose
> behalf the message was sent, not to the list.

I think that's a list setting, not a gmail one.

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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Brandon S. Allbery KF8NH

On Oct 1, 2008, at 15:51 , Andrew Coppin wrote:

wman wrote:
Long story short, I promised him a one-liner to "show the power and  
beauty of Haskell".


(writeFile "output.csv") =<< (liftM printCSV $ liftM (map  
updateLine) $ parseCSVFromFile "input.csv")


Is there room for improvement ?


Um... Does anybody else find it interesting that we are "showing the  
beauty of Haskell" by attempting to construct the most terse,  
cryptic, unmaintainable tangle of point-free code that the combined  
mindpower of the entire mailing list can produce?



To a certain geek mindset, that *is* the power and beauty.
(Then again, that's the mindset that publishes incomprehensible JAPHs  
in their .signature files.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread wman
Thats why i put those quotation marks around that part of sequence ;-))
AFAIK one-liners never were about comprehensibility, just about what you can
cram into one line of code.

Any programmer should have no problems guessing what the line does does
(even more so when looking at the "final" version without the abundant
liftM's), the beauty of it lies in figuring how the heck it does what it
does. And figuring that out should bring the "profound enlightenment
experience; that experience which should make you a better programmer for
the rest of your days, even if you never actually use Lisp -erm Haskell-
itself a lot" (my apologies, P. Graham, for cannibalizing your words).

I should probably get myself a signature stating that i will explicitly warn
the reader when being serious ;-)

PS: Sorry, Andrew, that I first posted the reply directly to you, still
getting used to the fact that gmail kindly replies to the user on whose
behalf the message was sent, not to the list.

On Wed, Oct 1, 2008 at 9:51 PM, Andrew Coppin
<[EMAIL PROTECTED]>wrote:

> wman wrote:
>
>> Long story short, I promised him a one-liner to "show the power and beauty
>> of Haskell".
>>
>> (writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
>> parseCSVFromFile "input.csv")
>>
>> Is there room for improvement ?
>>
>
> Um... Does anybody else find it interesting that we are "showing the beauty
> of Haskell" by attempting to construct the most terse, cryptic,
> unmaintainable tangle of point-free code that the combined mindpower of the
> entire mailing list can produce?
>
> Yes, there is much to be said for the power and brevity of Haskell. But you
> *can* go over the top here, people! o_O
>
> Keep it short _yet comprehensible_, IMHO.
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Andrew Coppin

wman wrote:
Long story short, I promised him a one-liner to "show the power and 
beauty of Haskell".


(writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) 
$ parseCSVFromFile "input.csv")


Is there room for improvement ?


Um... Does anybody else find it interesting that we are "showing the 
beauty of Haskell" by attempting to construct the most terse, cryptic, 
unmaintainable tangle of point-free code that the combined mindpower of 
the entire mailing list can produce?


Yes, there is much to be said for the power and brevity of Haskell. But 
you *can* go over the top here, people! o_O


Keep it short _yet comprehensible_, IMHO.

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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Derek Elkins
On Wed, 2008-10-01 at 10:15 +0200, Ketil Malde wrote:
> Derek Elkins <[EMAIL PROTECTED]> writes:
> 
> >> parseCSVFromFile "in.csv" >>= return . either (const "error!")
> 
> > Whenever you see this >>= return . f pattern think liftM or fmap or <$>.
> 
> ...and "return . f >>= action" is just "action . f", no?


Well actually that's \x -> action (return (f x)) x via the (r ->)
instance of Monad.  I think what you wanted was
\x -> return (f x) >>= action which is
\x -> action (f x)
action . f via the monad laws.

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


Re: [Haskell-cafe] csv one-liner

2008-10-01 Thread Ketil Malde
Derek Elkins <[EMAIL PROTECTED]> writes:

>> parseCSVFromFile "in.csv" >>= return . either (const "error!")

> Whenever you see this >>= return . f pattern think liftM or fmap or <$>.

...and "return . f >>= action" is just "action . f", no?

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


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Derek Elkins
On Tue, 2008-09-30 at 14:54 -0400, Graham Fawcett wrote:
> 2008/9/30 wman <[EMAIL PROTECTED]>:
> > I got asked how to do one particular thing in excel, which led to discssion
> > with "our local MSOffice expert".
> > During the discussion I stated that's it too much of a PITA and that I'd
> > rather write a script.
> > Long story short, I promised him a one-liner to "show the power and beauty
> > of Haskell".
> >
> > I got the csv package from hackage, modified the parseCSVFromFile so it's
> > returns IO CSV rather than IO (Either ParseError CSV), and finished with
> > following code
> >
> > (writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
> > parseCSVFromFile "input.csv")
> >
> > Is there room for improvement ?
> > Could it still be made into one-liner without modifying the csv module (and
> > without resorting to
> > case parseCSVFromFile "input.csv" of { Left _ -> []; Right x -> x}
> > kind of tricks) ?
> 
> How about:
> 
> parseCSVFromFile "in.csv" >>= return . either (const "error!")

Whenever you see this >>= return . f pattern think liftM or fmap or <$>.

> printCSV >>= writeFile "out.csv"

(either (const "error!") printCSV <$> parseCSVFromFile "in.csv") >>=
writeFile "out.csv"


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


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Henning Thielemann


On Tue, 30 Sep 2008, wman wrote:


Thanks a lot, I've had a hunch it was possible to get rid of those those
liftM's. I turned it into:

(writeFile "output.csv") . printCSV . (map updateLine) . (either (error "Chyba pri cteni CSV.") 
id) =<< parseCSVFromFile "input.csv"


You may even remove parentheses around 'writeFile', 'map' and 'either'.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread wman
True, true. And i told myself no-one would notice ;-))

On Tue, Sep 30, 2008 at 9:51 PM, Graham Fawcett <[EMAIL PROTECTED]>wrote:

> 2008/9/30 wman <[EMAIL PROTECTED]>:
> > Thanks a lot, I've had a hunch it was possible to get rid of those those
> > liftM's. I turned it into:
> >
> > (writeFile "output.csv") . printCSV . (map updateLine) . (either (error
> > "Chyba pri cteni CSV.") id) =<< parseCSVFromFile "input.csv"
> >
> > and am sincerely hoping he will try to decypher it's meaning ;-)))
>
> It looks like you've added some good error-czeching code here. :-;
>
> G
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Graham Fawcett
2008/9/30 wman <[EMAIL PROTECTED]>:
> Thanks a lot, I've had a hunch it was possible to get rid of those those
> liftM's. I turned it into:
>
> (writeFile "output.csv") . printCSV . (map updateLine) . (either (error
> "Chyba pri cteni CSV.") id) =<< parseCSVFromFile "input.csv"
>
> and am sincerely hoping he will try to decypher it's meaning ;-)))

It looks like you've added some good error-czeching code here. :-;

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


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread wman
Thanks a lot, I've had a hunch it was possible to get rid of those those
liftM's. I turned it into:

(writeFile "output.csv") . printCSV . (map updateLine) . (either (error
"Chyba pri cteni CSV.") id) =<< parseCSVFromFile "input.csv"

and am sincerely hoping he will try to decypher it's meaning ;-)))

On Tue, Sep 30, 2008 at 9:01 PM, Simon Brenner <[EMAIL PROTECTED]> wrote:

> Something like this perhaps:
>
> writeFile "output.csv" . printCSV . map updateLine . fromRight =<<
> parseCSVFromFile "input.csv"
>
> (with fromRight = either (error "fromRight :: Left") id or something
> equivalent)
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Simon Brenner
Something like this perhaps:

writeFile "output.csv" . printCSV . map updateLine . fromRight =<<
parseCSVFromFile "input.csv"

(with fromRight = either (error "fromRight :: Left") id or something equivalent)

On 9/30/08, wman <[EMAIL PROTECTED]> wrote:
> I got asked how to do one particular thing in excel, which led to discssion
> with "our local MSOffice expert".
> During the discussion I stated that's it too much of a PITA and that I'd
> rather write a script.
>  Long story short, I promised him a one-liner to "show the power and beauty
> of Haskell".
>
> I got the csv package from hackage, modified the parseCSVFromFile so it's
> returns IO CSV rather than IO (Either ParseError CSV), and finished with
> following code
>
> (writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
> parseCSVFromFile "input.csv")
>
> Is there room for improvement ?
> Could it still be made into one-liner without modifying the csv module (and
> without resorting to
>  case parseCSVFromFile "input.csv" of { Left _ -> []; Right x -> x}
> kind of tricks) ?
>
>
> Thanks, wman.
>
> ___
>  Haskell-Cafe mailing list
>  Haskell-Cafe@haskell.org
>  http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Dougal Stanton
2008/9/30 wman <[EMAIL PROTECTED]>:
> I got asked how to do one particular thing in excel, which led to discssion
> with "our local MSOffice expert".
> During the discussion I stated that's it too much of a PITA and that I'd
> rather write a script.
> Long story short, I promised him a one-liner to "show the power and beauty
> of Haskell".
>
> I got the csv package from hackage, modified the parseCSVFromFile so it's
> returns IO CSV rather than IO (Either ParseError CSV), and finished with
> following code
>
> (writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
> parseCSVFromFile "input.csv")
>
> Is there room for improvement ?
> Could it still be made into one-liner without modifying the csv module (and
> without resorting to
> case parseCSVFromFile "input.csv" of { Left _ -> []; Right x -> x}
> kind of tricks) ?
>

I have good news for you:

either :: (b ->c) (a -> c) (Either b a) -> c

That type signature is from memory, but you get the idea. You pass in
two functions - one to deal with the Left and the other to deal with
the Right, and it sorts out your result for you.

Cheers,

D


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


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Graham Fawcett
2008/9/30 wman <[EMAIL PROTECTED]>:
> I got asked how to do one particular thing in excel, which led to discssion
> with "our local MSOffice expert".
> During the discussion I stated that's it too much of a PITA and that I'd
> rather write a script.
> Long story short, I promised him a one-liner to "show the power and beauty
> of Haskell".
>
> I got the csv package from hackage, modified the parseCSVFromFile so it's
> returns IO CSV rather than IO (Either ParseError CSV), and finished with
> following code
>
> (writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
> parseCSVFromFile "input.csv")
>
> Is there room for improvement ?
> Could it still be made into one-liner without modifying the csv module (and
> without resorting to
> case parseCSVFromFile "input.csv" of { Left _ -> []; Right x -> x}
> kind of tricks) ?

How about:

parseCSVFromFile "in.csv" >>= return . either (const "error!")
printCSV >>= writeFile "out.csv"

using Data.Either (either) ?

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


Re: [Haskell-cafe] csv one-liner

2008-09-30 Thread Henning Thielemann


On Tue, 30 Sep 2008, wman wrote:


I got asked how to do one particular thing in excel, which led to discssion
with "our local MSOffice expert".
During the discussion I stated that's it too much of a PITA and that I'd
rather write a script.
Long story short, I promised him a one-liner to "show the power and beauty
of Haskell".

I got the csv package from hackage, modified the parseCSVFromFile so it's
returns IO CSV rather than IO (Either ParseError CSV), and finished with
following code

(writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
parseCSVFromFile "input.csv")

Is there room for improvement ?
Could it still be made into one-liner without modifying the csv module (and
without resorting to
case parseCSVFromFile "input.csv" of { Left _ -> []; Right x -> x}
kind of tricks) ?


The line will become a little longer, but you can wrap IO (Either ...) in 
an ErrorT, use its exception handling capability and unwrap the complete 
action. Or you replace 'case' on Either by 'either (const []) id' or 
'either (error "could not open file") id'.

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


[Haskell-cafe] csv one-liner

2008-09-30 Thread wman
I got asked how to do one particular thing in excel, which led to discssion
with "our local MSOffice expert".
During the discussion I stated that's it too much of a PITA and that I'd
rather write a script.
Long story short, I promised him a one-liner to "show the power and beauty
of Haskell".

I got the csv package from hackage, modified the parseCSVFromFile so it's
returns IO CSV rather than IO (Either ParseError CSV), and finished with
following code

(writeFile "output.csv") =<< (liftM printCSV $ liftM (map updateLine) $
parseCSVFromFile "input.csv")

Is there room for improvement ?
Could it still be made into one-liner without modifying the csv module (and
without resorting to
case parseCSVFromFile "input.csv" of { Left _ -> []; Right x -> x}
kind of tricks) ?


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