[Haskell-cafe] implementing a csv reader
Henning Thielemann
lemming at henning-thielemann.de
Tue Aug 22 05:26:45 EDT 2006
On Tue, 22 Aug 2006, Tamas K Papp wrote:
> Hi,
>
> Now that I have read the tutorials, I think that the best way to learn
> Haskell would be to use the language and write something simple yet
> useful. I noticed that Haskell lacks a module for reading/writing csv
> (comma separated value) files, so I thought I could implement that.
>
> Questions:
>
> 1. Please tell me if you know of a csv module, because then I would do
> something else.
see attachment
-------------- next part --------------
module Spreadsheet where
{-
See also
http://www.xoltar.org/languages/haskell.html
http://www.xoltar.org/languages/haskell/CSV.hs
-}
import Useful(chop,replace)
import Data.List(intersperse)
import Text.ParserCombinators.ReadP(ReadP)
import qualified Text.ParserCombinators.ReadP as Parser
toTable :: Char -> Char -> String -> [[String]]
toTable qm sep =
let parseChar :: ReadP Char
parseChar = Parser.choice
[Parser.satisfy (qm/=),
Parser.string [qm,qm] >> return qm]
parseQuoted :: ReadP String
parseQuoted = Parser.between (Parser.char qm) (Parser.char qm)
(Parser.many parseChar)
parseCell :: ReadP String
parseCell = Parser.choice [parseQuoted, return ""]
parseLine :: ReadP [String]
parseLine = Parser.sepBy (parseCell) (Parser.char sep)
parse str =
fromSingleton (map fst (filter (null . snd)
(Parser.readP_to_S parseLine str)))
in map parse . lines
fromSingleton :: [a] -> a
fromSingleton [x] = x
fromSingleton [] = error "fromSingleton: empty list."
fromSingleton _ = error "fromSingleton: list must contain at most one element."
fromTable :: Char -> Char -> [[String]] -> String
fromTable qm sep =
unlines . map (concat . intersperse [sep] .
map (\s -> [qm] ++ replace [qm] [qm,qm] s ++ [qm]))
toTableSimple :: Char -> Char -> String -> [[String]]
toTableSimple qm sep =
map (map (dequote qm) . chop (sep==)) . lines
fromTableSimple :: Char -> Char -> [[String]] -> String
fromTableSimple qm sep =
unlines . map (concat . intersperse [sep] . map (\s -> [qm]++s++[qm]))
dequote :: Eq a => a -> [a] -> [a]
dequote _ [] = error "dequote: string is empty"
dequote q (x:xs) =
if x == q && last xs == q
then init xs
else error "dequote: string not correctly quoted"
More information about the Haskell-Cafe
mailing list