[Haskell-beginners] [Code Review] csv file to sqlite3

aditya siram aditya.siram at gmail.com
Thu Jul 28 04:19:09 CEST 2011


Hi Shakthi,
Are you aware that there is a csv parsing package on Hackage? If
you're writing the parser as a exercise, Real World Haskell [1] has a
chapter on Parsec that covers csv parsing.
-deech

[1] http://book.realworldhaskell.org/read/using-parsec.html

On Wed, Jul 27, 2011 at 9:12 PM, Shakthi Kannan <shakthimaan at gmail.com> wrote:
> Hi,
>
> I am trying to write a simple Haskell program to read from a .csv file
> and write to a .sqlite3 database. Can anyone please review the
> following code?
>
> === BEGIN ===
>
> import Text.ParserCombinators.Parsec
>
> import Database.HDBC
> import Database.HDBC.Sqlite3
> import Control.Monad(when)
>
> -- | Initialize DB and return database Connection
> connect :: FilePath -> IO Connection
> connect fp =
>    do dbh <- connectSqlite3 fp
>       prepDB dbh
>       return dbh
>
> prepDB :: IConnection conn => conn -> IO ()
> prepDB dbh =
>       do tables <- getTables dbh
>          when (not ("entries" `elem` tables)) $
>               do run dbh "CREATE TABLE entries ( \
>                  \id INTEGER NOT NULL PRIMARY KEY AUTOINCREMENT, \
>                  \first TEXT, \
>                  \second TEXT, \
>                  \third TEXT)" []
>                  return ()
>          commit dbh
>
> csvFile = endBy line eol
> line = sepBy cell (char ';')
> cell = quotedCell <|> many (noneOf ";\n\r")
>
> quotedCell =
>    do char '"'
>       content <- many quotedChar
>       char '"' <?> "quote at end of cell"
>       return content
>
> quotedChar =
>           noneOf "\""
>    <|> try (string "\"\"" >> return '"')
>
> eol =   try (string "\n\r")
>    <|> try (string "\r\n")
>    <|> string "\n"
>    <|> string "\r"
>    <?> "end of line"
>
>
> process :: [String] -> IO ()
> process r = do
>        conn <- connectSqlite3 "simple1.db"
>        run conn "INSERT INTO entries (first, second, third) VALUES
> (?, ?, ?)" (map toSql r)
>        commit conn
>        disconnect conn
>
> main = do
>     dbh <- connect "simple1.db"
>     do c <- getContents
>        case parse csvFile "(stdin)" c of
>             Left e -> do putStrLn "Error parsing input:"
>                          print e
>             Right r -> do
>                   mapM_ process r
>
> === END ===
>
> Appreciate any suggestions, improvements in this regard.
>
> Thanks!
>
> SK
>
> --
> Shakthi Kannan
> http://www.shakthimaan.com
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list