[web-devel] [ Newbie ] [ MongoDB ] Using MongoDB Persistent backend

Greg Weber greg at gregweber.info
Thu Jun 30 17:55:24 CEST 2011


I think it is about time to finally fix this. I am probably the least
knowledgeable about Monad mashing, but seems like a good time to learn!

Here is a simple app we can use:
https://gist.github.com/1056520

But maybe it is best to use the test suite. Here are all the hacks to get
the tests to run right now that need to be removed:

instance Context DB.MasterOrSlaveOk IO where
  context = undefined
  push = undefined
instance Context DB.Database IO where
  context = undefined
  push = undefined
instance Context DB.WriteMode IO where
  context = undefined
  push = undefined
instance Context DB.Pipe IO where
  context = undefined
  push = undefined
instance Control.Monad.Throw.Throw DB.Failure IO where
  throw = undefined
  catch = undefined


On Wed, Jun 29, 2011 at 1:25 AM, Michael Snoyman <michael at snoyman.com>wrote:

> On Wed, Jun 29, 2011 at 11:17 AM, Kamil Ciemniewski
> <ciemniewski.kamil at gmail.com> wrote:
> > Hi all,
> >
> > I've got some "newbie" problems using MongoDB as backend
> > in Persistent.
> >
> > Basically I've got my app type defined as:
> > data MyApp = MyApp
> >     { getStatic :: Static -- ^ Settings for static file serving.
> >     , connPool :: ConnPool Host
> >     }
> >
> > And I made it an instance of YesodPersist by:
> > instance YesodPersist MyApp where
> >   type YesodDB MyApp = MongoDBReader Host
> >   runDB db = liftIOHandler
> >            $ fmap connPool getYesod >>= (\p -> return (p, "localhost"))
> >>=
> > runMongoDBConn db
> >
> > And I made it an instance of YesodAuth as well by:
> > instance YesodAuth MyApp where
> >   type AuthId MyApp = UserId
> >
> >   loginDest _ = RootR
> >   logoutDest _ = RootR
> >
> >   getAuthId creds = runDB $ do
> >       x <- getBy $ UniqueUser $ credsIdent creds
> >       case x of
> >       Just (uid, _) -> return $ Just uid
> >       Nothing -> do
> >           fmap Just $ insert $ User (credsIdent creds) Nothing
> >
> >   authPlugins = [ authEmail ]
> >
> > I've defined User model as yesod scaffold tool defines it.
> >
> > Now, when I try to compile it i get:
> >
> > No instances for (Control.Monad.Context.Context
> >                         Database.MongoDB.Connection.MasterOrSlaveOk
> >                         (GGHandler s MyApp IO),
> >                       Control.Monad.Context.Context
> >                         Database.MongoDB.Query.Database (GGHandler s
> MyApp
> > IO),
> >                       Control.Monad.Context.Context
> >                         Database.MongoDB.Internal.Protocol.Pipe
> (GGHandler s
> > MyApp IO),
> >                       Control.Monad.Context.Context
> >                         Database.MongoDB.Query.WriteMode (GGHandler s
> MyApp
> > IO),
> >                       Control.Monad.Throw.Throw
> >                         Database.MongoDB.Query.Failure (GGHandler s MyApp
> > IO))
> >       arising from a use of `insert'
> >     Possible fix:
> >       add instance declarations for
> >       (Control.Monad.Context.Context
> >          Database.MongoDB.Connection.MasterOrSlaveOk
> >          (GGHandler s MyApp IO),
> >        Control.Monad.Context.Context
> >          Database.MongoDB.Query.Database (GGHandler s MyApp IO),
> >        Control.Monad.Context.Context
> >          Database.MongoDB.Internal.Protocol.Pipe (GGHandler s MyApp IO),
> >        Control.Monad.Context.Context
> >          Database.MongoDB.Query.WriteMode (GGHandler s MyApp IO),
> >        Control.Monad.Throw.Throw
> >          Database.MongoDB.Query.Failure (GGHandler s MyApp IO))
> >     In the expression: insert
> >     In the second argument of `($)', namely
> >       `insert $ User (credsIdent creds) Nothing'
> >     In the expression:
> >         fmap Just $ insert $ User (credsIdent creds) Nothing
> >
> > The problem is probably very trivial.. But I've got no ideas how to fix
> it.
> >
> > Best regards
> > Kamil Ciemniewski
> >
> > _______________________________________________
> > web-devel mailing list
> > web-devel at haskell.org
> > http://www.haskell.org/mailman/listinfo/web-devel
> >
> >
>
> I don't have direct experience with the MongoDB backend, but I can
> give this a shot if I saw some code. I think one possibility would be
> to wrap everything in a liftIO, but then you won't have access to the
> Handler monad features. This would prevent you from doing things like
> setting messages and sending redirects from the database access
> itself, but should otherwise be fine.
>
> Michael
>
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110630/538ba241/attachment-0001.htm>


More information about the web-devel mailing list