[yesod] using presistance in sub sites

Hi there! I'm a bit confused on how to use persistence in a sub site... I've written this here, which fails to compile: https://gist.github.com/1058863 Is it possible at all to define persistence functionality on subsite level and then use the masters runDB ? Whats best practice here? I've seen yesod-auth let implement the persistance related stuff over a type class in the master ... But I'd like to keep that stuff with the subsite... Ideas, comments anyone? Thanks Markus

On Fri, Jul 1, 2011 at 7:27 PM, Markus Barenhoff
Hi there!
I'm a bit confused on how to use persistence in a sub site...
I've written this here, which fails to compile: https://gist.github.com/1058863
Is it possible at all to define persistence functionality on subsite level and then use the masters runDB ? Whats best practice here?
I've seen yesod-auth let implement the persistance related stuff over a type class in the master ... But I'd like to keep that stuff with the subsite...
Ideas, comments anyone?
Thanks Markus
_______________________________________________ web-devel mailing list web-devel@haskell.org http://www.haskell.org/mailman/listinfo/web-devel
It's a good question. The answer is far from intuitive; I played around with type errors until I got something to work. Hope this helps: {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, GeneralizedNewtypeDeriving #-} {-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-} {-# LANGUAGE DeriveDataTypeable, NoMonomorphismRestriction, FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} import Data.Text (Text) import Language.Haskell.TH.Syntax hiding (lift) import Yesod share2 mkPersist (mkMigrate "migrateTest") [persist| Test foo Text |] data TestSite = TestSite mkYesodSub "TestSite" [ ClassP ''YesodPersist [VarT $ mkName "master"] , ClassP ''PersistBackend [ ConT ''YesodDB `AppT` VarT (mkName "master") `AppT` (ConT ''GGHandler `AppT` ConT ''TestSite `AppT` VarT (mkName "master") `AppT` ConT ''IO) ] ] [parseRoutes| /insert InsertR POST |] postInsertR :: (YesodPersist master, PersistBackend (YesodDB master (GGHandler sub master IO))) => GHandler sub master () postInsertR = do runDB $ insert $ Test "bar" return () Michael
participants (2)
-
Markus Barenhoff
-
Michael Snoyman