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

2011-06-21 Thread David Virebayre
2011/5/2 Bryan O'Sullivan b...@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=, 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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread cheater cheater
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+hask...@gmail.com wrote:
 2011/5/2 Bryan O'Sullivan b...@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=, 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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___

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

2011-06-21 Thread Johan Tibell
On Tue, Jun 21, 2011 at 2:34 PM, cheater cheater cheate...@gmail.com wrote:
 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?

Not at the moment. I believe Bryan has at least talked with one other
author (of a PostreSQL binding) about perhaps sharing an API in the
future.

My opinions is that we should wait to consolidate APIs/standardize
interfaces until we actually have an idea what a good Haskell API for
databases looks like. To know that we need to seem some different
ones.

Cheers,
Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread Christopher Done
On 21 June 2011 13:45, David Virebayre dav.vire+hask...@gmail.com wrote:
 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

Yeah, the first example is wrong. Indeed. Should be fixed. I forgot to
tell Bryan about that. I noticed it was wrong when I first looked at
it but it's still tripping people up.

You can access the docs on a slightly earlier version:
http://hackage.haskell.org/package/mysql-simple-0.2.2.0

 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.

The doc specifies it here:

 convertError :: [Field] - [Maybe ByteString] - Int - a
 Throw a ConversionFailed exception, indicating a mismatch between the number 
 of columns in the Field and row, and the number in the collection to be 
 converted to.

So if you're making an instance for a type that takes ten items from
the collection, then put 10. Could always make this clearer.

 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)

Ah, I wouldn't know about that, I haven't used the mysql version.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread David Virebayre
 You can access the docs on a slightly earlier version:
 http://hackage.haskell.org/package/mysql-simple-0.2.2.0

That's what I did.

 The doc specifies it here:

 convertError :: [Field] - [Maybe ByteString] - Int - a
 Throw a ConversionFailed exception, indicating a mismatch between the number 
 of columns in the Field and row, and the number in the collection to be 
 converted to.

 So if you're making an instance for a type that takes ten items from
 the collection, then put 10. Could always make this clearer.

That wasn't clear to me, but English isn't my first language, so maybe
that's why.


 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)
 Ah, I wouldn't know about that, I haven't used the mysql version.

I tried again with that code:


data PlateauSel = PS
  { psPlat :: Int
  , psArm :: Maybe Int
  , psTaille :: Int
  , psType :: Int
  , psEtat :: Int
  , psLoc :: Int
  , psDest :: Int
  , psCol :: Int
  , psEtg :: Int
  , psNiv :: Int
  , psPos :: Int
  , psRes :: Int
  }

instance QueryResults PlateauSel where
  convertResults [fa,fb,fc,fd,fe,ff,fg,fh,fi,fj,fk,fl]
 [va,vb,vc,vd,ve,vf,vg,vh,vi,vj,vk,vl]
 = PS a b c d e f g h i j k l
where !a = convert fa va
  !b = convert fb vb
  !c = convert fc vc
  !d = convert fd vd
  !e = convert fe ve
  !f = convert ff vf
  !g = convert fg vg
  !h = convert fh vh
  !i = convert fi vi
  !j = convert fj vj
  !k = convert fk vk
  !l = convert fl vl
  convertResults fs vs = convertError fs vs 12
hello :: IO [PlateauSel]
hello = do
  conn - connect myConnectInfo
  query_ conn call Plateau_Select(1)


But there's no improvement :

*Main hello
*** Exception: ConnectionError {errFunction = query, errNumber =
1312, errMessage = PROCEDURE robot.Plateau_Select can't return a
result set in the given context}
*Main

The problem isn't with the stored procedure, it works if I call it
from the mysql client.

(@x.x.x.x) [robot] (;) call Plateau_Select(1);
+---+---++--+--+--+-+-+---++--+-+
| IdPlateau | IdArmoire | Taille | Type | Etat | Localisation |
Destination | Colonne | Etage | Niveau | Position | Reserve |
+---+---++--+--+--+-+-+---++--+-+
| 1 |  NULL |  1 |2 |1 |1 |
   1 |   0 | 0 |  0 |0 |   1 |
+---+---++--+--+--+-+-+---++--+-+
1 row in set (0.03 sec)

Another information: it doesn't work either with HDBC-mysql, but it
does work with HDBC-odbc.





Another unrelated thing : the documentation states that the Query type
is designed to make it difficult to create queries by concatenating
strings.
I found out there are situations where you don't have a choice.

For example, how to write a function that returns the columns of a
table using show columns ?

type Champ = (String,String,String,String,String,String)
getColumns :: Connection - String - IO [Champ]
getColumns conn table = do
  query_ conn (fromString $ show columns from  ++ table)

if you try query conn show columns from  ( Only table), the query built is
show columns from 'x'
which fails.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread Christopher Done
On 21 June 2011 16:47, David Virebayre dav.vire+hask...@gmail.com wrote:
 For example, how to write a function that returns the columns of a
 table using show columns ?

 type Champ = (String,String,String,String,String,String)
 getColumns :: Connection - String - IO [Champ]
 getColumns conn table = do
  query_ conn (fromString $ show columns from  ++ table)

 if you try query conn show columns from  ( Only table), the query built is
 show columns from 'x'
 which fails.

For this you could have

newtype Entity = Entity String

and implement the Param class for this type which will output the
string in double quotes, and then you can write:

query conn SHOW COLUMNS FROM ? (Only mytable)

(With OverloadedStrings enabled.)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread Christopher Done
On 21 June 2011 16:54, Christopher Done chrisd...@googlemail.com wrote:
 query conn SHOW COLUMNS FROM ? (Only mytable)

 (With OverloadedStrings enabled.)

Woops, that would need a type annotation. (Only (mytable :: Entity))

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread Johan Tibell
On Tue, Jun 21, 2011 at 4:47 PM, David Virebayre
dav.vire+hask...@gmail.com wrote:
 The problem isn't with the stored procedure, it works if I call it
 from the mysql client.

Does mysql-simple support stored procedures?

Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread Bryan O'Sullivan
On Tue, Jun 21, 2011 at 4:45 AM, David Virebayre dav.vire+hask...@gmail.com
 wrote:


 I had trouble accessing the documentation : the last versions on
 hackage have a build failure, so the doc isn't available.


I don't understand why that build failure occurs. You can always build
documentation for a package locally using cabal haddock.


 The very first example didn't work for me :


Oops, thanks for mentioning that. I've fixed the documentation and made the
information about type inference a little clearer.

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.


Thanks for spotting the omission, I've clarified that. The Int parameter
indicates the number of columns expected for conversion.


 I'm not sure if that means Database.MySQL supports calling stored
 procedures that return a result set or not. I suspect not.


The mysql-simple package currently doesn't support stored procedures or
multi-statement queries. Each of these can return multiple result sets. It
would be necessary to add new functions to the API to support them, as of
course each result set could have a different shape.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-06-21 Thread Bryan O'Sullivan
On Tue, Jun 21, 2011 at 7:47 AM, David Virebayre dav.vire+hask...@gmail.com
 wrote:

 The problem isn't with the stored procedure, it works if I call it
 from the mysql client.


Right - as I mentioned in my previous note, the problem is that stored
procedures and multi-statement queries can both return multiple result sets.
We can't easily use type inference to express the difference between in
this use of query, I want a single result (the common case) and in this
other use of query, I expect three results, each with different shapes (far
less common), so we need something like a multiQuery function (and perhaps a
MultiResult class) instead.

Another unrelated thing : the documentation states that the Query type
 is designed to make it difficult to create queries by concatenating
 strings.


You can do it, but you have to use the Monoid class's functions, e.g.:
select  `mappend` 2 + 2

For cases like your show columns from example, though, I prefer Chris's
suggestion of creating a custom newtype with its own special Param instance.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2011-05-01 Thread Bryan O'Sullivan
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.

   - Performance: compared to HDBC-mysql, mysql-simple yields a 60%
   performance improvement on my real-world application.
   - Ease of use: compared again to HDBC, my real-world application's
   DB-specific code shrunk by 50% while achieving the above performance
   increase.
   - Type safety: it's intentionally hard to construct SQL queries by string
   concatenation, but of course I provide some nice safe APIs for formatting
   queries and converting results. That safety does not come at the expense of
   performance or expressive bloat, as the above results indicate.

Because I know that some people favour interacting with their databases via
a model such as iteratees, the mysql-simple library is built on top of a
very lightweight library.

That lower-level library is named mysql:
http://hackage.haskell.org/package/mysql

This is a low-level binding to the MySQL client API. It is aimed at high
performance and simplicity, but more specifically for consumption by authors
of higher-level database libraries. It is bare enough of features that it
doesn't even perform conversion between Haskell and SQL types, but at the
same time it uses bytestrings sensibly, cheaply avoids some nasty signal
interruption problems with the MySQL client library, and abstracts some of
the tiresome details of memory management. It gives a higher-level library
complete control over result conversion, how to fetch results, and all that,
so you can focus purely on building iteratees and not the lower-level gunk.

Enjoy!
B.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe