Type classes and definite types

Hi folks, I set out to perform a (seemingly) simple experiment last night. I thought I'd try to get used to the HSQL library by writing a little app that would take an SQL query on the command line, run it, and print the results. So far, this seems to be impossible. I'd like to know if there's a way around this problem, or if this is actually insurmountable (short of generating and compiling new Haskell programs for each query). The HSQL library works quite well for queries whose types you know in advance, as in printRow stmt = do (id :: Int) <- getFieldValue stmt "ID" (code :: String) <- getFieldValue stmt "Code" (name :: String) <- getFieldValue stmt "Name" putStrLn (unwords [show id, show code, show name]) however, it doesn't work at all if you can't specify the types at compile time: printRow' (names,types,nulls) stmt = do values <- mapM (getFieldValue stmt) names putStrLn $ unwords (map show values) The problem is that getFieldValue returns a value of type (SqlBind a) => a. That is, there's no type information associated with this return value other than it's a valid SQL value. There are no operations in the SqlBind class, it's just a marker as near as I can tell. So when you call getFieldValue, the exact type has to be fixed in some way (by annotations in this example). If the type is not fixed, it can't be used, as shown by the fact that printRow' won't compile. I think this is just the same problem we have with other type classes, e.g., (show (read s)), not anything new. The question is, what can be done about it? Is there anything I, the user can do about it, or can only the library authors solve this problem? Is there something we can change in Haskell to make this sort of thing possible? Thanks, Bryn import Database.HSQL import Database.HSQL.ODBC import System.Environment (getArgs) main = do (connString:sql:_) <- getArgs conn <- connect connString "" "" putStrLn "Connected" stmt <- query conn sql putStrLn $ "Ran query " ++ sql let info = unzip3 $ getFieldsTypes stmt putStrLn (show info) forEachRow' printRow stmt printRow stmt = do (id :: Int) <- getFieldValue stmt "ID" (code :: String) <- getFieldValue stmt "Code" (name :: String) <- getFieldValue stmt "Name" putStrLn (unwords [show id, show code, show name]) printRow' (names,types,nulls) stmt = do values <- mapM (getFieldValue stmt) names putStrLn $ unwords (map show values)

Bryn Keller
Hi folks, Hello, [skip] The problem is that getFieldValue returns a value of type (SqlBind a) => a. That is, there's no type information associated with this return value other than it's a valid SQL value. There are no operations in the SqlBind class, it's just a marker as near as I can tell. As of HSQL 1.4 this class has method toSqlValue :: a -> String which probably can help you (I really don't know).
Some RTFSing shows that in most cases toSqlValue is implemented with show. -- WBR, Max Vasin.

Max Vasin wrote:
Bryn Keller
writes: Hi folks,
Hello, [skip]
The problem is that getFieldValue returns a value of type (SqlBind a) => a. That is, there's no type information associated with this return value other than it's a valid SQL value. There are no operations in the SqlBind class, it's just a marker as near as I can tell.
As of HSQL 1.4 this class has method toSqlValue :: a -> String which probably can help you (I really don't know).
Some RTFSing shows that in most cases toSqlValue is implemented with show.
Hi Max, Thanks for pointing this out. It's odd that I don't see that anywhere in the docs at the HToolkit site: http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC certainly believes it exists. However, this doesn't actually solve the problem. Substituting toSqlValue for show in printRow' gives the same compile error: Main.hs:22:18: Ambiguous type variable `a' in the constraint: `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30 Probable fix: add a type signature that fixes these type variable(s) So, like with (show (read s)), we still can't use the function until we've established a definite type for the value, not just a type class. Bryn

Bryn Keller
Hi Max, Hello Bryn,
Thanks for pointing this out. It's odd that I don't see that anywhere in the docs at the HToolkit site: http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC certainly believes it exists. However, this doesn't actually solve the problem. Substituting toSqlValue for show in printRow' gives the same compile error:
Main.hs:22:18: Ambiguous type variable `a' in the constraint: `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30 Probable fix: add a type signature that fixes these type variable(s)
So, like with (show (read s)), we still can't use the function until we've established a definite type for the value, not just a type class. Yeah... Some more RTFSing shows that we have the
getFieldValueType :: Statement -> String -> (SqlType, Bool) which allows us to write printRow stmt = do (id :: Int) <- getFieldValue stmt "ID" let (codeType, _) = getFieldValueType stmt "Code" codestr <- case codeType of SqlChar _ -> do (c :: String) <- getFieldValue stmt "Code" return (toSqlValue c) SqlInteger -> do (i :: Int) <- getFieldValue stmt "Code" return (toSqlValue i) -- etc for all SqlType data constructors putStrLn (unwords [show id, codestr]) At least it compiles. But it's ugly :-( -- WBR, Max Vasin.

Max Vasin wrote:
Bryn Keller
writes: Hi Max,
Hello Bryn,
Thanks for pointing this out. It's odd that I don't see that anywhere in the docs at the HToolkit site: http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC certainly believes it exists. However, this doesn't actually solve the problem. Substituting toSqlValue for show in printRow' gives the same compile error:
Main.hs:22:18: Ambiguous type variable `a' in the constraint: `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30 Probable fix: add a type signature that fixes these type variable(s)
So, like with (show (read s)), we still can't use the function until we've established a definite type for the value, not just a type class.
Yeah... Some more RTFSing shows that we have the
getFieldValueType :: Statement -> String -> (SqlType, Bool)
which allows us to write
printRow stmt = do (id :: Int) <- getFieldValue stmt "ID" let (codeType, _) = getFieldValueType stmt "Code" codestr <- case codeType of SqlChar _ -> do (c :: String) <- getFieldValue stmt "Code" return (toSqlValue c) SqlInteger -> do (i :: Int) <- getFieldValue stmt "Code" return (toSqlValue i) -- etc for all SqlType data constructors putStrLn (unwords [show id, codestr])
At least it compiles. But it's ugly :-(
Ah, good point! Ugly it may be, but at least it works. Thanks for the idea! Bryn

Hi Bryn Keller,
The solution for your problem is very simple. You just have to fetch
all values as strings. In this way the library will do all required
conversions for you.
printRow stmt = do
id <- getFieldValue stmt "ID"
code <- getFieldValue stmt "Code"
name <- getFieldValue stmt "Name"
putStrLn (unwords [id, code, name])
Cheers,
Krasimir
On 5/6/05, Bryn Keller
Max Vasin wrote:
Bryn Keller
writes: Hi Max,
Hello Bryn,
Thanks for pointing this out. It's odd that I don't see that anywhere in the docs at the HToolkit site: http://htoolkit.sourceforge.net/doc/hsql/Database.HSQL.html but GHC certainly believes it exists. However, this doesn't actually solve the problem. Substituting toSqlValue for show in printRow' gives the same compile error:
Main.hs:22:18: Ambiguous type variable `a' in the constraint: `SqlBind a' arising from use of `getFieldValue' at Main.hs:22:18-30 Probable fix: add a type signature that fixes these type variable(s)
So, like with (show (read s)), we still can't use the function until we've established a definite type for the value, not just a type class.
Yeah... Some more RTFSing shows that we have the
getFieldValueType :: Statement -> String -> (SqlType, Bool)
which allows us to write
printRow stmt = do (id :: Int) <- getFieldValue stmt "ID" let (codeType, _) = getFieldValueType stmt "Code" codestr <- case codeType of SqlChar _ -> do (c :: String) <- getFieldValue stmt "Code" return (toSqlValue c) SqlInteger -> do (i :: Int) <- getFieldValue stmt "Code" return (toSqlValue i) -- etc for all SqlType data constructors putStrLn (unwords [show id, codestr])
At least it compiles. But it's ugly :-(
Ah, good point! Ugly it may be, but at least it works. Thanks for the idea!
Bryn _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Bryn Keller
-
Krasimir Angelov
-
Max Vasin