CSV parser, quotes?

Shawn P. Garbett listman@garbett.org
Wed, 30 Jul 2003 14:54:35 -0500


In attempting to improve the CSV parser based on comments, I have the 
following code that's attached. I'm having a heck of a time getting the 
double quotes = an escaped quote thing to work. There is some commented out 
code which was my last attempt. As it stands the code works, minus the 
escaped quotes. Remove the comments and it just hangs.

module CSV (contents, csv) where

import Parsec

----------------------------------------------------------------------
-- CSV Module 
----------------------------------------------------------------------

-- Useful common parsers
comma :: Parser Char
comma  = char ','

quote :: Parser Char
quote  = char '\"'

-- How to handle these buggers....
--esc_quote :: Parser Char
--esc_quote  = do {char '\"'; char '\"';}

--text      :: Parser String
--text       = do {esc_quote; t<-text; return ('\"':t)}
--             <|> do {c <- noneOf "\""; t<-text; return (c:t) } 
--             <|> return ""

-- A cell can be a quoted value, a number or empty
-- Quotes can be embedded by using double quotes ""
cell      :: Parser String
cell       = between quote quote (many (noneOf "\"")) -- quoted values
--cell       = between quote quote text -- quoted values
             <|> many1 (noneOf "\",\n")               -- unquoted values
             <|> return ""                            -- give up, Empty cell   

-- Group of cells with a newline
cells     :: Parser [String]
cells      = do c <- sepBy cell comma
                newline
                return c

-- Comma Separated Values, set of rows followed by eof
csv       :: Parser [[String]]
csv        = manyTill cells eof

-- Useful For extracting comma delimited values of a cell
contents  :: Parser [String]
contents   = sepBy1 (many (noneOf ",")) comma