
Dear Group, Greetings. I have a feeling that what I am trying to do is easy, I just don't know how to say it in Haskell. Let's start with:
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
import Database.HDBC import Data.Typeable (Typeable) import Data.Data data C = C { str :: String, dbl:: Double } deriving (Eq, Ord, Typeable, Data)
a :: C a = C "twelve" 12.0
Now I load this up in ghci and I can do the following: toSql . str $ a -- result: SqlString "twelve" toSql . dbl $ a -- result: SqlDouble 12.0 but what I would really like to do is something like: gmapQ toSql $ a which results in: <interactive>:1:7: Could not deduce (Convertible d SqlValue) arising from a use of `toSql' from the context (Data d) bound by a type expected by the context: Data d => d -> SqlValue at <interactive>:1:1-11 Possible fix: add (Convertible d SqlValue) to the context of a type expected by the context: Data d => d -> SqlValue or add an instance declaration for (Convertible d SqlValue) In the first argument of `gmapQ', namely `toSql' In the expression: gmapQ toSql In other words, I'm looking for a function with a signature: (Whatever Instances I neeed here) => a -> [SqlValue] I have tried various incantations of type signatures, but thus far I can't get it right. Can someone point me in the right direction? Thanks. Henry Laxen -- Nadine & Henry Laxen Belle, Venus, Aphrodite 10580 N. McCarran Blvd. Adonis, Miss Parker & Jarod Suite 115-396 Via Alta # 6 Reno, Nevada Chapala, Jalisco, Mexico 89503-1896 CP 45900 The rest is silence. (Hamlet)

Hmm, this is a bit peculiar. The problem is you don't get control over how gmapQ invokes the function toSql: it will only ever be done with the type signature Data d => d -> u. There is good reason for this too: imagined you tried to run gmapQ toSql on a data-type that contained a member that was not convertible to a SqlValue: then it ought to fail with a type error! You may be able to work around this with more generics madness: use Typeable to check if the types of all the fields are kosher, and then do an appropriate casts before invoking toSql. But you won't get particularly good static guarantees doing it this way. So... what are you really trying to do? :-) Edward Excerpts from nadine.and.henry's message of Sun Apr 24 10:21:03 -0400 2011:
Dear Group,
Greetings. I have a feeling that what I am trying to do is easy, I just don't know how to say it in Haskell. Let's start with:
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
import Database.HDBC import Data.Typeable (Typeable) import Data.Data data C = C { str :: String, dbl:: Double } deriving (Eq, Ord, Typeable, Data)
a :: C a = C "twelve" 12.0
Now I load this up in ghci and I can do the following:
toSql . str $ a -- result: SqlString "twelve" toSql . dbl $ a -- result: SqlDouble 12.0
but what I would really like to do is something like:
gmapQ toSql $ a
which results in: <interactive>:1:7: Could not deduce (Convertible d SqlValue) arising from a use of `toSql' from the context (Data d) bound by a type expected by the context: Data d => d -> SqlValue at <interactive>:1:1-11 Possible fix: add (Convertible d SqlValue) to the context of a type expected by the context: Data d => d -> SqlValue or add an instance declaration for (Convertible d SqlValue) In the first argument of `gmapQ', namely `toSql' In the expression: gmapQ toSql
In other words, I'm looking for a function with a signature:
(Whatever Instances I neeed here) => a -> [SqlValue]
I have tried various incantations of type signatures, but thus far I can't get it right. Can someone point me in the right direction? Thanks.
Henry Laxen

Thanks for the quick reply Edward. What I'm trying to do is be lazy. I have a longish data structure, say: data Loan = Loan { loan_address :: String, loan_initialAmount :: Double, loan_interestRate :: Double, loan_term:: Int, loan_originated :: Day, loan_minimumPayment :: Double, loan_usualPayment :: Double, loan_familiarName :: String, loan_password :: String, loan_lastVisit :: Day, loan_nextToLastVisit :: Day, loan_emailAddress :: String, } deriving (Read, Show, Eq, Ord, Typeable, Data) where each component is an instance of (Convertible a SqlValue), and I would like to be able to say something like: let vals = magicalGmapIncantation toSql loan liftIO $ withtransaction db $ \d -> run query vals of course I could do: let vals = [toSql (loan_address loan), toSql (loan_initialAmount loan) ...] but that feels so "dirty," when all those fields are just waiting for me inside that loan data type. Best wishes, H
"EZY" == Edward Z Yang
writes:
EZY> Hmm, this is a bit peculiar. The problem is you don't get control EZY> over how gmapQ invokes the function toSql: it will only ever be done EZY> with the type signature Data d => d -> u. There is good reason for EZY> this too: imagined you tried to run gmapQ toSql on a data-type that EZY> contained a member that was not convertible to a SqlValue: then it EZY> ought to fail with a type error! EZY> You may be able to work around this with more generics madness: use EZY> Typeable to check if the types of all the fields are kosher, and then EZY> do an appropriate casts before invoking toSql. But you won't get EZY> particularly good static guarantees doing it this way. EZY> So... what are you really trying to do? :-) ------------------------------------------------------------------------ Greetings. I have a feeling that what I am trying to do is easy, I just don't know how to say it in Haskell. Let's start with:
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
import Database.HDBC import Data.Typeable (Typeable) import Data.Data data C = C { str :: String, dbl:: Double } deriving (Eq, Ord, Typeable, Data)
a :: C a = C "twelve" 12.0
Now I load this up in ghci and I can do the following: toSql . str $ a -- result: SqlString "twelve" toSql . dbl $ a -- result: SqlDouble 12.0 but what I would really like to do is something like: gmapQ toSql $ a which results in: <interactive>:1:7: Could not deduce (Convertible d SqlValue) arising from a use of `toSql' from the context (Data d) bound by a type expected by the context: Data d => d -> SqlValue at <interactive>:1:1-11 Possible fix: add (Convertible d SqlValue) to the context of a type expected by the context: Data d => d -> SqlValue or add an instance declaration for (Convertible d SqlValue) In the first argument of `gmapQ', namely `toSql' In the expression: gmapQ toSql In other words, I'm looking for a function with a signature: (Whatever Instances I neeed here) => a -> [SqlValue] I have tried various incantations of type signatures, but thus far I can't get it right. Can someone point me in the right direction? Thanks. -- Nadine & Henry Laxen Belle, Venus, Aphrodite 10580 N. McCarran Blvd. Adonis, Miss Parker & Jarod Suite 115-396 Via Alta # 6 Reno, Nevada Chapala, Jalisco, Mexico 89503-1896 CP 45900 The rest is silence. (Hamlet)

"EZY" == Edward Z Yang
writes:
EZY> Where did 'query' come from? Edward I left that out because it was just a prebuilt db query. It came from something like: dataNames :: Data a => a -> [String] dataNames = constrFields . toConstr loanNames = datanames (loan :: Loan) {- yielding: ["loan_address","loan_initialAmount","loan_interestRate","loan_term","loan_originated","loan_minimumPayment","loan_usualPayment","loan_familiarName","loan_password","loan_lastVisit","loan_nextToLastVisit","loan_emailAddress"] -} let query = "INSERT INTO loans (" ++ loanNames ++ ") values (" ++ (intercalate ", " (replicate (length loanNames) "?")) ++ ")" Best wishes, H

Not that it solves your problem, but you may want to take a look at persistent [1]. Cheers, [1] http://hackage.haskell.org/package/persistent -- Felipe.
participants (3)
-
Edward Z. Yang
-
Felipe Almeida Lessa
-
nadine.and.henry@pobox.com