<div dir="ltr"><div>Here's how it works, every time you supply a query, you supply the parameters to the query in a tuple.  Furthermore the results can be gotten back as a tuple by type hinting each value.  Warning:  I have not run this code, but it should be close.<br></div><div><br></div><div>query "select age, is_old from user where uid = ? and name = ? (uid :: Int, name :: String)  :: IO [(Integer, Bool)]</div><div><br></div><div>But what happens when you want to supply a single parameter (or receive a single value?)</div><div><br></div><div>query "select * from user where uid = ?" (uid)</div><div><br></div><div>The problem with that is (uid) is not a tuple.  It's just an integer in parenthesis.  There in fact is no way to specify a tuple of one length.  So mysql-simple (and other libraries) very often have a single type meant to be used as a single element tuple.  In mysql-simple's (and postgresql-simple) case that is the (Only a) type.  (Side note, I wish these were in the standard Tuple module, as this comes once in awhile).<br></div><div><br></div><div>query "select name from user where uid = ?" (Only uid) :: IO [Only String]</div><div><br></div><div>Remember that you can also make your own records implement the <a id="gmail-t:QueryParams" class="gmail-def">QueryParams </a><a id="gmail-t:QueryResults" class="gmail-def">and QueryResults classes so that you can write <br></a></div></div><br><div class="gmail_quote"><div dir="ltr">On Mon, Dec 3, 2018 at 6:22 AM Damien Mattei <<a href="mailto:mattei@oca.eu">mattei@oca.eu</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">{-# LANGUAGE OverloadedStrings #-}<br>
<br>
import Database.MySQL.Simple<br>
import Control.Monad<br>
import Data.Text as Text<br>
import Data.Int<br>
<br>
<br>
main :: IO ()<br>
main = do<br>
  conn <- connect defaultConnectInfo<br>
    { connectHost = "moita",<br>
      connectUser = "mattei",<br>
      connectPassword = "******",<br>
      connectDatabase = "sidonie" }<br>
<br>
  rows <- query_ conn "select `N° BD` from sidonie.Coordonnées where Nom<br>
= 'A    20'"<br>
<br>
  --putStrLn $ show rows<br>
<br>
  forM_ rows $ \(fname, lname) -><br>
     putStrLn $  fname ++ " " ++ Text.unpack lname ++ " "<br>
<br>
<br>
here is the error:<br>
<br>
*Main> :load Toto<br>
[1 of 1] Compiling Main             ( Toto.hs, interpreted )<br>
Ok, one module loaded.<br>
*Main> main<br>
*** Exception: ConversionFailed {errSQLType = "1 values:<br>
[(VarString,Just \"-04.3982\")]", errHaskellType = "2 slots in target<br>
type", errFieldName = "[\"N\\194\\176 BD\"]", errMessage = "mismatch<br>
between number of columns to convert and number in target type"}<br>
<br>
-04.3982 is the values i want to put in a variable,it's the N° BD<br>
(Durchmusterung Number)<br>
<br>
<br>
???<br>
<br>
any help greatly appeciated ;-)<br>
<br>
<br>
-- <br>
<a href="mailto:Damien.Mattei@unice.fr" target="_blank">Damien.Mattei@unice.fr</a>, <a href="mailto:Damien.Mattei@oca.eu" target="_blank">Damien.Mattei@oca.eu</a>, UNS / OCA / CNRS<br>
_______________________________________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org" target="_blank">Beginners@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners</a><br>
</blockquote></div>