database access,extracting result...

{-# LANGUAGE OverloadedStrings #-} import Database.MySQL.Simple import Control.Monad import Data.Text as Text import Data.Int main :: IO () main = do conn <- connect defaultConnectInfo { connectHost = "moita", connectUser = "mattei", connectPassword = "******", connectDatabase = "sidonie" } rows <- query_ conn "select `N° BD` from sidonie.Coordonnées where Nom = 'A 20'" --putStrLn $ show rows forM_ rows $ \(fname, lname) -> putStrLn $ fname ++ " " ++ Text.unpack lname ++ " " here is the error: *Main> :load Toto [1 of 1] Compiling Main ( Toto.hs, interpreted ) Ok, one module loaded. *Main> main *** Exception: ConversionFailed {errSQLType = "1 values: [(VarString,Just \"-04.3982\")]", errHaskellType = "2 slots in target type", errFieldName = "[\"N\\194\\176 BD\"]", errMessage = "mismatch between number of columns to convert and number in target type"} -04.3982 is the values i want to put in a variable,it's the N° BD (Durchmusterung Number) ??? any help greatly appeciated ;-) -- Damien.Mattei@unice.fr, Damien.Mattei@oca.eu, UNS / OCA / CNRS

just find myself this solution: main :: IO () main = do conn <- connect defaultConnectInfo { connectHost = "moita", connectUser = "mattei", connectPassword = "****", connectDatabase = "sidonie" } rows <- query_ conn "select `N° BD` from sidonie.Coordonnées where Nom = 'A 20'" forM_ rows $ \(Only a) -> putStrLn $ Text.unpack a Le 03/12/2018 12:21, Damien Mattei a écrit :
{-# LANGUAGE OverloadedStrings #-}
import Database.MySQL.Simple import Control.Monad import Data.Text as Text import Data.Int
main :: IO () main = do conn <- connect defaultConnectInfo { connectHost = "moita", connectUser = "mattei", connectPassword = "******", connectDatabase = "sidonie" }
rows <- query_ conn "select `N° BD` from sidonie.Coordonnées where Nom = 'A 20'"
--putStrLn $ show rows
forM_ rows $ \(fname, lname) -> putStrLn $ fname ++ " " ++ Text.unpack lname ++ " "
here is the error:
*Main> :load Toto [1 of 1] Compiling Main ( Toto.hs, interpreted ) Ok, one module loaded. *Main> main *** Exception: ConversionFailed {errSQLType = "1 values: [(VarString,Just \"-04.3982\")]", errHaskellType = "2 slots in target type", errFieldName = "[\"N\\194\\176 BD\"]", errMessage = "mismatch between number of columns to convert and number in target type"}
-04.3982 is the values i want to put in a variable,it's the N° BD (Durchmusterung Number)
???
any help greatly appeciated ;-)
-- Damien.Mattei@unice.fr, Damien.Mattei@oca.eu, UNS / OCA / CNRS

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.
query "select age, is_old from user where uid = ? and name = ? (uid :: Int,
name :: String) :: IO [(Integer, Bool)]
But what happens when you want to supply a single parameter (or receive a
single value?)
query "select * from user where uid = ?" (uid)
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).
query "select name from user where uid = ?" (Only uid) :: IO [Only String]
Remember that you can also make your own records implement the QueryParams and
QueryResults classes so that you can write
On Mon, Dec 3, 2018 at 6:22 AM Damien Mattei
{-# LANGUAGE OverloadedStrings #-}
import Database.MySQL.Simple import Control.Monad import Data.Text as Text import Data.Int
main :: IO () main = do conn <- connect defaultConnectInfo { connectHost = "moita", connectUser = "mattei", connectPassword = "******", connectDatabase = "sidonie" }
rows <- query_ conn "select `N° BD` from sidonie.Coordonnées where Nom = 'A 20'"
--putStrLn $ show rows
forM_ rows $ \(fname, lname) -> putStrLn $ fname ++ " " ++ Text.unpack lname ++ " "
here is the error:
*Main> :load Toto [1 of 1] Compiling Main ( Toto.hs, interpreted ) Ok, one module loaded. *Main> main *** Exception: ConversionFailed {errSQLType = "1 values: [(VarString,Just \"-04.3982\")]", errHaskellType = "2 slots in target type", errFieldName = "[\"N\\194\\176 BD\"]", errMessage = "mismatch between number of columns to convert and number in target type"}
-04.3982 is the values i want to put in a variable,it's the N° BD (Durchmusterung Number)
???
any help greatly appeciated ;-)
-- Damien.Mattei@unice.fr, Damien.Mattei@oca.eu, UNS / OCA / CNRS _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

thank you David, i did something like that: rows <- query_ conn "SELECT Nom,distance FROM AngularDistance WHERE distance > 0.000278" forM_ rows $ \(name,distance) -> putStrLn $ Text.unpack name ++ " " ++ show (distance :: Double) output: ... HJ 2900 3.333333333882682e-2 HJ 3340 1.6666666646205367e-2 HLD 73 1.666666666807325e-2 HLD 152 1.666666666807325e-2 HLD 158 1.666666666807325e-2 HO 6 0.19569724135990224 HO 15 1.666666666807325e-2 ... and it works Damien Le 03/12/2018 15:42, David McBride a écrit :
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.
query "select age, is_old from user where uid = ? and name = ? (uid :: Int, name :: String) :: IO [(Integer, Bool)]
But what happens when you want to supply a single parameter (or receive a single value?)
query "select * from user where uid = ?" (uid)
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).
query "select name from user where uid = ?" (Only uid) :: IO [Only String]
Remember that you can also make your own records implement the QueryParams and QueryResults classes so that you can write
On Mon, Dec 3, 2018 at 6:22 AM Damien Mattei
mailto:mattei@oca.eu> wrote: {-# LANGUAGE OverloadedStrings #-}
import Database.MySQL.Simple import Control.Monad import Data.Text as Text import Data.Int
main :: IO () main = do conn <- connect defaultConnectInfo { connectHost = "moita", connectUser = "mattei", connectPassword = "******", connectDatabase = "sidonie" }
rows <- query_ conn "select `N° BD` from sidonie.Coordonnées where Nom = 'A 20'"
--putStrLn $ show rows
forM_ rows $ \(fname, lname) -> putStrLn $ fname ++ " " ++ Text.unpack lname ++ " "
here is the error:
*Main> :load Toto [1 of 1] Compiling Main ( Toto.hs, interpreted ) Ok, one module loaded. *Main> main *** Exception: ConversionFailed {errSQLType = "1 values: [(VarString,Just \"-04.3982\")]", errHaskellType = "2 slots in target type", errFieldName = "[\"N\\194\\176 BD\"]", errMessage = "mismatch between number of columns to convert and number in target type"}
-04.3982 is the values i want to put in a variable,it's the N° BD (Durchmusterung Number)
???
any help greatly appeciated ;-)
-- Damien.Mattei@unice.fr mailto:Damien.Mattei@unice.fr, Damien.Mattei@oca.eu mailto:Damien.Mattei@oca.eu, UNS / OCA / CNRS _______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Damien.Mattei@unice.fr, Damien.Mattei@oca.eu, UNS / OCA / CNRS
participants (2)
-
Damien Mattei
-
David McBride