[web-devel] Yesod CRUD Help

Michael Snoyman michael at snoyman.com
Wed Apr 6 05:50:09 CEST 2011


Hi Francisco,

There's a few issues at play here, all of which should be addressed in the
documentation. As a historical note, I should mention that I had actually
dropped support for the CRUD module a bit ago, and added it back by request.
It works, but isn't very customizable. If you're not scared off by that,
read on!

The first problem (the error message you're getting) is because mkToForm is
not meant to be called like that. Instead, you need to call it after the
entity definitions as its own TH splice, like so:

mkToForm (undefined :: Entry)

Now, GHC will complain about a stage restriction. Basically, there are
certain things you can't refer to from TH in the same file in which they
were defined, and type class instances is one of them. The solution is to
move the entity declaration to a separate file (Model.hs, attached).

Next, defaultCrud can't be passed as-is to the routing system, since it
gives no indication what datatype should be used. Instead, you need to
define one that uses explicit types:

entryCrud :: Blog -> Crud Blog Entry
entryCrud = defaultCrud

And then pass that to the routing:

/admin          AdminR EntryCrud entryCrud

The only other thing I changed was fixing the indentation in getRootR,
though I'm guessing that was a copy-paste issue. I also didn't fix it
particularly well, I leave that as an exercise to the reader ;).

HTH,
Michael

On Tue, Apr 5, 2011 at 7:57 PM, Francisco Jose CHAVES ALONSO <
pachopepe at gmail.com> wrote:

> Hi
>
> In order to know how the CRUD works, I was trying the blog example of the
> Screencast, updated to yesod 7 but the mkToForm
> gives me the following error:
>
> No instance for (PersistEntity [Database.Persist.Base.EntityDef])
>      arising from a use of `mkToForm'
>    Possible fix:
>      add an instance declaration for
>      (PersistEntity [Database.Persist.Base.EntityDef])
>    In the expression: mkToForm
>    In the first argument of `share', namely
>      `[mkToForm, mkPersist, mkMigrate "migrateAll"]'
>    In the expression:
>      share
>        [mkToForm, mkPersist, mkMigrate "migrateAll"]
>        [Database.Persist.Base.EntityDef
>           "Entry"
>           []
>           [("title", "String", []), ("day", "Day", ["Desc"]), ....]
>           []
>           []]
>
> Any suggestion?
>
> Thanks in advance
>
> Francisco
>
> The code is:
>
> {-# LANGUAGE TypeFamilies, QuasiQuotes, GeneralizedNewtypeDeriving,
> TemplateHaskell, MultiParamTypeClasses #-}
> import Yesod
> import Yesod.Helpers.Crud
> import Database.Persist
> import Database.Persist.Sqlite
> import Database.Persist.TH
> import Data.Time (Day)
> import Network.Wai.Middleware.Debug (debug)
> import Network.Wai.Handler.Warp (run)
>
> share [mkToForm, mkPersist, mkMigrate "migrateAll"] [persist|
> Entry
>    title String
>    day Day Desc
>    content Html
>    deriving
> |]
>
>
> -- Necesary for CRUD
> instance Item Entry where
>    itemTitle = entryTitle
>
> data Blog = Blog { pool :: ConnectionPool }
>
> type EntryCrud = Crud Blog Entry
>
> mkYesod "Blog" [parseRoutes|
> /               RootR  GET
> /entry/#EntryId EntryR GET
> -- Subsite
> /admin          AdminR EntryCrud defaultCrud
> |]
>
> instance Yesod Blog where
>    approot _ = "http://localhost:3000"
>
> instance YesodPersist Blog where
>    type YesodDB Blog = SqlPersist
>    runDB db = liftIOHandler $ fmap pool getYesod >>= runSqlPool db
>
> getRootR = do
>        entries <- runDB $ selectList [] [EntryDayDesc] 0 0
>        defaultLayout $ do
>            setTitle $ string "Yesod Blog Tutorial Homepage"
>            [hamlet|
> <h1> Archive
> <ul>
>    $forall entry <- entries
> <li>
> <a href="@{EntryR (fst entry)}">#{entryTitle (snd entry)}
> <p>
> <a href="@{AdminR CrudListR}">Admin
> |]
>
> getEntryR entryid = do
>    entry <- runDB $ get404 entryid
>    defaultLayout $ do
>        setTitle $ string $ entryTitle entry
>        [hamlet|
> <h1> #{entryTitle entry}
> <h2> #{show (entryDay entry)}
> #{entryContent entry}
> |]
>
> withBlog :: (Application -> IO a) -> IO a
> withBlog f = withSqlitePool "blog.db3" 8 $ \pool -> do
>    flip runSqlPool pool $ do
>        (runMigration migrateAll)
>        insert $ Entry "First Entry" (read "2011-04-04")
>               $ preEscapedString "<h3>First Entry</h3>"
>    let h = Blog pool
>    toWaiApp h >>= f
>
> main = withBlog $ run 3000 . debug
>
>
> _______________________________________________
> 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/20110406/4ad730c1/attachment.htm>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: Model.hs
Type: text/x-haskell
Size: 346 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110406/4ad730c1/attachment.hs>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: test.hs
Type: text/x-haskell
Size: 1890 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110406/4ad730c1/attachment-0001.hs>


More information about the web-devel mailing list