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

Kamil Ciemniewski ciemniewski.kamil at gmail.com
Wed Jun 29 10:17:00 CEST 2011


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110629/c544ea52/attachment.htm>


More information about the web-devel mailing list