[ Newbie ] [ MongoDB ] Using MongoDB Persistent backend

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

Its not trivial. Apparently, the mongodb driver isn't exactly ready for showtime. AFAIK, the context monad is a reader monad that contains the connection parameters for mongo. I never got it to work. Greg might know more. Max On Jun 29, 2011, at 4:17 PM, Kamil Ciemniewski 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@haskell.org http://www.haskell.org/mailman/listinfo/web-devel

On Wed, Jun 29, 2011 at 11:17 AM, Kamil Ciemniewski
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@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

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
On Wed, Jun 29, 2011 at 11:17 AM, Kamil Ciemniewski
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@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@haskell.org http://www.haskell.org/mailman/listinfo/web-devel

OK, simple question: why can't we use a type of MongoDBReader of:
newtype MongoDBReader m a = MongoDBReader (Action m a)
deriving (Monad, Trans.MonadIO, Functor, Applicative)
Michael
On Thu, Jun 30, 2011 at 6:55 PM, Greg Weber
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
wrote: On Wed, Jun 29, 2011 at 11:17 AM, Kamil Ciemniewski
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@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@haskell.org http://www.haskell.org/mailman/listinfo/web-devel

The latest version of persistent-mongoDB on hackage works now. After we get
some more usage it will be added as a scaffolding option. Here is some basic
runner code:
import Database.Persist.MongoDB
import Database.MongoDB.Connection
import qualified Database.MongoDB as DB
runMongo :: MongoDBReader (GGHandler M M IO) a -> GHandler M M a
runMongo x = liftIOHandler $
withMongoDBConn (DB.Database "test") "127.0.0.1" $ runMongoDBConn x
DB.safe DB.Master
On Thu, Jun 30, 2011 at 11:26 AM, Michael Snoyman
OK, simple question: why can't we use a type of MongoDBReader of:
newtype MongoDBReader m a = MongoDBReader (Action m a) deriving (Monad, Trans.MonadIO, Functor, Applicative)
Michael
On Thu, Jun 30, 2011 at 6:55 PM, Greg Weber
wrote: 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
wrote: On Wed, Jun 29, 2011 at 11:17 AM, Kamil Ciemniewski
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@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@haskell.org http://www.haskell.org/mailman/listinfo/web-devel

I upgraded persistent-mongoDB for Persisten 0.6. I also added it to the
scaffolding, although there is still an issue with the scaffolded site. I am
going to try to upgrade persistent-mongoDB to use the new MongoDB 1.0
driver and then fix the scaffolding.
On Thu, Jul 7, 2011 at 8:30 AM, Greg Weber
The latest version of persistent-mongoDB on hackage works now. After we get some more usage it will be added as a scaffolding option. Here is some basic runner code:
import Database.Persist.MongoDB import Database.MongoDB.Connection import qualified Database.MongoDB as DB
runMongo :: MongoDBReader (GGHandler M M IO) a -> GHandler M M a runMongo x = liftIOHandler $ withMongoDBConn (DB.Database "test") "127.0.0.1" $ runMongoDBConn x DB.safe DB.Master
On Thu, Jun 30, 2011 at 11:26 AM, Michael Snoyman
wrote: OK, simple question: why can't we use a type of MongoDBReader of:
newtype MongoDBReader m a = MongoDBReader (Action m a) deriving (Monad, Trans.MonadIO, Functor, Applicative)
Michael
On Thu, Jun 30, 2011 at 6:55 PM, Greg Weber
wrote: 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
wrote: On Wed, Jun 29, 2011 at 11:17 AM, Kamil Ciemniewski
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@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@haskell.org http://www.haskell.org/mailman/listinfo/web-devel
participants (4)
-
Greg Weber
-
Kamil Ciemniewski
-
Max Cantor
-
Michael Snoyman