[Takusen] working out how to use bind variables

Jason Dagit dagit at codersbase.com
Wed Aug 18 02:48:52 EDT 2010


On Tue, Aug 17, 2010 at 6:46 PM, Michael Litchard <michael at schmong.org>wrote:

> Thanks for everyone's help. Here is where I'm at right now.
>
> > import Database.PostgreSQL.Enumerator
> > import Database.Enumerator
> > import Control.Monad.Trans
>
> > insertPair :: (String, Int) -> DBM mark s Int
> > insertPair act_entry = (execDML (cmdbind "insert into activities
> (Activity, Cost) values (?, ?)" [bindP activity, bindP cost]))
> >     where activity = fst act_entry
> >           cost     = snd act_entry
>
> > main :: IO ()
> > main = do
> >  let connection = connect [CAdbname "tutorialDB"]
> >  withSession connection $ do
> >  let activities :: [(String, Int)]
> >      activities = [("Golf", 47), ("Sailing", 50), ("Squash", 40),
> ("Swimming", 15), ("Tennis", 36)]
> >  execDDL (sql "create table activities (Activity char(20) PRIMARY KEY,
> cost int)")
>
> >  return $ liftIO $ map insertPair activities
>
> The errors I receive are these.
>

I modified your program in two ways, see here:

> import Database.PostgreSQL.Enumerator
> import Database.Enumerator
> import Control.Monad.Trans

> insertPair :: (String, Int) -> DBM mark Session Int

Here I changed the `s' to `Session'.  More about that below.

> insertPair act_entry = (execDML (cmdbind "insert into activities
(Activity, Cost) values (?, ?)" [bindP activity, bindP cost]))
>     where activity = fst act_entry
>           cost     = snd act_entry

> main :: IO ()
> main = do
>  let connection = connect [CAdbname "tutorialDB"]
>  withSession connection $ do
>  let activities :: [(String, Int)]
>      activities = [("Golf", 47), ("Sailing", 50), ("Squash", 40),
("Swimming", 15), ("Tennis", 36)]
>  execDDL (sql "create table activities (Activity char(20) PRIMARY KEY,
cost int)")

>  sequence_ $ map insertPair activities

The way to go from DBM to IO is to use withSession.  If we apply insertPair
to a pair (of the right type), then we get an action in the DB monad, or in
other words, we get something with DBM in the type.  liftIO goes the other
way.  It takes something that is IO and gives you something with DBM in the
type (actually, liftIO is more general, but that's what it will do in this
context).  And since, we're mapping insertPair over a list of activities we
get a list of DB actions.  The way to run a list of monadic actions is to
use either sequence or sequence_.  Here since, we don't care about the
result I use sequence_ and the return was also causing problems.


>
> tutorial.lhs:6:26:
>    Could not deduce (Command
>                        Database.PostgreSQL.Enumerator.CommandBind s)
>      from the context ()
>

Normally, this error message is GHC's way of saying, "Hey, I figured out *a*
possible type class you could add to the type signature to make it type
check."  Due to a design decision for Takusen, the CommandBind class is not
exported from the backend.  That means we have to do something different
here than the advice they give next.


>      arising from a use of `execDML' at tutorial.lhs:6:26-127
>    Possible fix:
>      add (Command
>             Database.PostgreSQL.Enumerator.CommandBind s) to the context of
>        the type signature for `insertPair'
>      or add an instance declaration for
>         (Command Database.PostgreSQL.Enumerator.CommandBind s)
>    In the expression:
>         (execDML
>           (cmdbind
>              "insert into activities (Activity, Cost) values (?, ?)"
>               [bindP activity, bindP cost]))
>    In the definition of `insertPair':
>        insertPair act_entry
>                      = (execDML
>                          (cmdbind
>                             "insert into activities (Activity, Cost) values
> (?,
>  ?)"
>                              [bindP activity, bindP cost]))
>                     where
>                         activity = fst act_entry
>
>
>
So, instead of doing what was just recommended, let's look at the export
list of Database.PostgreSQL.Enumerator:

> module Database.PostgreSQL.Enumerator
>   ( Session, connect, ConnectAttr(..)
>   , prepareStmt, preparePrefetch
>   , prepareQuery, prepareLargeQuery, prepareCommand
>   , sql, sqlbind, prefetch, cmdbind
>   , bindType, DBAPI.byteaEsc, DBAPI.byteaUnesc
>   , DBAPI.UUID, DBAPI.string2uuid, DBAPI.uuid2string
>   , module Database.Enumerator
>   )
> where

Hm...`Session' is the first thing in that list.  Now let's double check how
the DBM type is defined:
> newtype IE.ISession sess => DBM mark sess a = DBM (ReaderT sess IO a)

Ah, ha.  So, DBM takes a session as the 2nd type parameter.  Oh, but we just
saw that Database.PostgreSQL.Enumerator exports `Session'.  And voila!  We
just plug that in and it works for your chosen backend.

I hope that helps.

I'm not sure how you would write it in a backend agnostic way.  I tried
using ISession in the type, but I received essentially the same error
message.  Then I tried adding (Command stmt s, ISession s) => ..., to the
type but that lead to other errors.  Does anyone know how you'd make this
polymorphic across backends?

Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://projects.haskell.org/pipermail/takusen/attachments/20100817/9fab085e/attachment.htm 


More information about the Takusen mailing list