Designing a Haskell database interface

Tim Docker timd@macquarie.com.au
Tue, 15 Jul 2003 02:26:57 +1000


I wrote an experimental wrapper around the sybase db client
libraries. This was my first attempt at using the ffi, and I was
impressed with the fact that I got enough working purely using
haskell.

My simplistic approach was to embed everything in the IO
monad, wrapping each sybase call trivially, and then building
slightly higher level functions on top of each. Of course, the
fun with handling queries is that you want to get values of types
defined by the query string (ie unknown at compile time) from the
database and into the typed haskell world.

In my approach, the top level interface looked like:

    open :: String -> String -> String -> IO Process
    -- open a connection to the database returning an abstract
    -- process object
    
    doquery :: Process -> String -> IO v -> IO [v]
    -- Takes: a db process; the SQL query string; and
    -- a (no parameter) IO action that, when executed
    -- during a query returns a value of type v derived
    -- from the "current" row
    --
    -- Returns the list of values of type v derived from
    -- each row.
    
    stringv :: Process -> CInt -> IO String
    doublev :: Process -> CInt -> IO Double
    intv    :: Process -> CInt -> IO Int
    datetimev :: Process -> CInt -> IO DateTime
    -- Returns the string/double/int/datetime value of the specified
    -- column in the "current" row

You could then write queries something like this:

    dbp <- DB.open "SERVER" "user" "password"
    rows <- DB.doquery dbp queryText $ do
          name <- DB.stringv dbp 1
          v1 <- DB.doublev dbp 2
          v2  <- DB.doublev dbp 3
          return (label,v1,v2)

At which point rows would have type [(String,Double,Double)].

This did the job, but I'd be interested in better ways of doing it!

Tim

> -----Original Message-----
> From: Bayley, Alistair [mailto:Alistair_Bayley@ldn.invesco.com]
> Sent: Monday, July 14, 2003 4:25 PM
> To: haskell-cafe@haskell.org
> Subject: Designing a Haskell database interface
> 
> 
> I'm making slow progress on an Oracle OCI binding. I've got the noddy
> session setup and database connection stuff working, so now 
> I'm looking at
> how results should be returned from SQL queries. In Haskell, 
> there doesn't
> seem to be any consistent way of returning results from SQL 
> queries, unlike
> (say) Java's JDBC interface. It may be a bit early to propose 
> a standard SQL
> dbms interface design, but... does anyone have any idea(s) 
> about how one
> ought to look?
> 
> Here's a simple survey of the sql dbms interfaces I've come 
> across so far (I
> found HaskellDB the most complex, and difficult to understand). My
> assumptions about how these various libraries work might be 
> quite wrong:
> 
> 
> HaskellDB:
>   dbQuery returns IO [row r],  where
>    - dbQuery is implemented by adoQuery (this library uses Odbc):
>        adoQuery :: IConnection () -> PrimQuery -> Rel r -> IO 
> [AdoRow r]
>    - "AdoRow a" is an instance of class Row
>    - "class Row row a" declares one function: rowSelect
>        rowSelect :: Attr r a -> row r -> a
>    - type AdoRow implements rowSelect with adoRowSelect:
>        adoRowSelect :: Variant a => Attr r a -> AdoRow r -> a
>    - Attr has one constructor: Attr Attribute, and Attribute is just a
> synonym for String.
>   So (I think) the return types are determined by the types 
> of the phantom
> types in "Attr r a" and "AdoRow r". And this is where my head 
> explodes...
> 
> 
> LibPQ:
>   fetchAllRows returns tuple pair of the connection and row :  (DBI a,
> [[String]])
>    - so, a row is a list of list of Strings.
> 
> 
> HaSql:
>   haSQLObtainQueryResults returns SQL [a], where 
>    - SQL is some custom IO+State Monad
>    - the type of a is the return type of a function you pass to
> haSQLObtainQueryResults to (I think) convert an Odbc pointer 
> into a Haskell
> type.
> 
> 
> MySql-hs:
>   mysqlQuery returns a tuple of (Integral, [[Maybe String]], 
> [MysqlField]),
> where
>    - the first element (Integral type) is the number of rows
>    - the second element is a list of list of Strings - the result set.
>    - the third element is metadata. MysqlField is a record 
> describing a
> database column.
> 
> 
> The most sophisticated implementation wrt type information seems to be
> HaskellDB. My initial goal was to use this library and 
> provide an Oracle
> database driver for it, but the HaskellDB seems to be quite 
> dependent on
> Trex, which AFAICT is a Hugs library.
> 
> I was thinking of splitting it into two parts: a library that 
> submits SQL
> queries and returns the results, and a library that 
> constructs queries with
> the relational calculus and generates SQL from them. The 
> relational calculus
> bit was what I was interested in, but for now I want to work 
> on getting data
> out of my Oracle database.
> 
> 
> Also...
> 
> I was wondering how you might go about mapping arbitrary dbms 
> types to a
> Haskell result set.
> 
> In an ideal world, you can store any values you like in a "relational"
> database. However, most SQL dbms products give you just 
> numbers, text, and
> dates. Some dbms's (PostgreSql and Oracle) allow 
> users/programmers to create
> new types and let the dbms treat them in the same manner as 
> the built-in
> ones i.e. with equality and ordering predicates, and 
> indexing. The built-in
> support for the three basic types (numbers, text, dates) is 
> reflected in the
> JDBC API; it has methods like: getByte, getShort, getFloat, getDouble,
> getBigDecimal, getInt, getString, getDate, getTime, 
> getBoolean, while other
> types are handled by methods like getBinaryStream and getObject.
> 
> So how would you convert a (say) PostgreSql Point or Box 
> value to a Haskell
> type? Would the approach taken by HaSql be the best (the user 
> provides a
> function that converts binary data into a Haskell value)?
> 
> 
> *****************************************************************
> The information in this email and in any attachments is 
> confidential and intended solely for the attention and use 
> of the named addressee(s). This information may be 
> subject to legal professional or other privilege or may 
> otherwise be protected by work product immunity or other 
> legal rules.  It must not be disclosed to any person without 
> our authority.
> 
> If you are not the intended recipient, or a person 
> responsible for delivering it to the intended recipient, you 
> are not authorised to and must not disclose, copy, 
> distribute, or retain this message or any part of it.
> *****************************************************************
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>