[Haskell-cafe] [ANN] mysql-simple - your go-to package for talking to MySQL

cheater cheater cheater00 at gmail.com
Tue Jun 21 14:34:17 CEST 2011


Hi,
does the package adhere to some form of standard API that works the
same way across other similar packages (different mysql drivers,
postgres, mongo, couch, etc)?

Is there such a standard for haskell?

D.

On Tue, Jun 21, 2011 at 13:45, David Virebayre
<dav.vire+haskell at gmail.com> wrote:
> 2011/5/2 Bryan O'Sullivan <bos at serpentine.com>:
>> Hi, folks -
>> Over the past few days, I've released two MySQL-related packages on Hackage
>> that I think should be pretty useful.
>> The first is mysql-simple: http://hackage.haskell.org/package/mysql-simple
>> This is a mid-level binding to the MySQL client API. I aimed it squarely at
>> being both fast and easy to use, and I'm very pleased with the results so
>> far.
>
> Hello,
>
> Some feedback about a very first try with your library;
>
> First of all, thanks a lot for releasing it, I hope it'll make many
> people's life easier.
> Also, thanks for taking the time to write a nice, thorough documentation.
>
> The library was easy to install, thanks to cabal -- no troubles here.
>
> I had trouble accessing the documentation : the last versions on
> hackage have a build failure, so the doc isn't available. I was able
> to see the documentation for mysql-simple-0.2.2.0 though.
>
> The very first example didn't work for me :
> ------------------------
> {-# LANGUAGE OverloadedStrings #-}
>
>  import Database.MySQL.Simple
>
>  hello = do
>   conn <- connect defaultConnectInfo
>   query conn "select 2 + 2"
> ------------------------
>   Couldn't match expected type `IO b'
>           against inferred type `q -> IO [r]'
>    In the expression: query conn "select 2 + 2"
>    In the expression:
>        do { conn <- connect defaultConnectInfo;
>             query conn "select 2 + 2" }
>    In the definition of `hello':
>        hello = do { conn <- connect defaultConnectInfo;
>                     query conn "select 2 + 2" }
>
> Using query_ instead of query brings a new error:
>
>   Ambiguous type variable `r' in the constraint:
>      `Database.MySQL.Simple.QueryResults.QueryResults r'
>        arising from a use of `query_' at ftmsql.hs:7:3-28
>    Possible cause: the monomorphism restriction applied to the following:
>      hello :: IO [r] (bound at ftmsql.hs:5:1)
>    Probable fix: give these definition(s) an explicit type signature
>                  or use -XNoMonomorphismRestriction
>
> Easily corrected, adding the pragma.
> Next step was to try it, which took me a few steps:
>
> *Main> hello
>
> <interactive>:1:0:
>    Ambiguous type variable `r' in the constraint:
>      `Database.MySQL.Simple.QueryResults.QueryResults r'
>        arising from a use of `hello' at <interactive>:1:0-4
>    Probable fix: add a type signature that fixes these type variable(s)
>
> *Main> hello :: IO [Only Int]
> *** Exception: Incompatible {errSQLType = "LongLong", errHaskellType =
> "Int", errMessage = "types incompatible"}
>
> *Main> hello :: IO [Only Int64]
>
> <interactive>:1:18: Not in scope: type constructor or class `Int64'
>
> etc.
>
> I would like to suggest modifying the exemple in the documentation to
> look like this
> ----------------------------------------------------------
> {-# LANGUAGE OverloadedStrings #-}
>
> import Database.MySQL.Simple
> import Data.Int
>
> myConnectInfo = defaultConnectInfo { connectHost = "x.x.x.x",
> connectUser= "xx", connectPassword="xxxx", connectDatabase="xxx" }
>
> hello :: IO [Only Int64]
> hello = do
>  conn <- connect myConnectInfo
>  query_ conn "select 2 + 2"
> ----------------------------------------------------------
> That way a beginner has a starting point that compiles and that he can
> run as is.
>
>
>
> Next I modified the simple example to call a stored procedure, it
> returns a resultset of 12 columns.
> Unfortunately, I realised that QueryResults instances are defined up
> to 10 elements only.
> However, the documentation shows how to define a QueryResults
> instance, so I created a datatype and tried to define the instance,
> and got stuck with an error:
>
>    Couldn't match expected type `PlateauSel'
>           against inferred type `Int -> a'
>    In the expression: convertError fs vs
>    In the definition of `convertResults':
>        convertResults fs vs = convertError fs vs
>    In the instance declaration for `QueryResults PlateauSel'
>
> Indeed, the documentation shows that convertError takes 3 parameters,
> and I gave, as per the example, only 2.
> But I'm not sure what to write for the 3rd parameter, the
> documentation doesn't help me here.
>
> To try, I put 0, and the test compiled. However, I had a connection
> error number 1312, saying my procedure "can't return a result set in
> the given context". (The query I used works from the mysql
> command-line interface)
>
> I'm not sure if that means Database.MySQL supports calling stored
> procedures that return a result set or not. I suspect not. Perhaps it
> would be useful to add it in the documentation.
>
> Thanks,
>
> David.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list