[web-devel] Call for comments: Yesod 0.2

Victor Nazarov asviraspossible at gmail.com
Wed May 12 14:57:08 EDT 2010


On Wed, May 12, 2010 at 5:46 PM, Michael Snoyman <michael at snoyman.com> wrote:
> Hi all,
> I believe my 0.2 branch of Yesod[1] is feature-complete for this release,
> and it seems to be fairly stable. The documentation on it[2] give a good
> introduction, and hopefully the haddocks will fill in the gaps.
> At this point, I wanted to ask the community if they have any changes they'd
> like to see in this release. I'm planning on releasing some time next week.
> The main feature which is still prominently missing for this release is a
> persistence layer; hopefully that will be included in the next major
> release. If anyone has any ideas on this, I'm all ears.
> Thanks,
> Michael
> [1] http://github.com/snoyberg/yesod/tree/ver0.2
> [2] http://docs.yesodweb.com/yesod/
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel
>
>

Following current Yesod design my wishlist is the follwing.

1. Get read of quasy quotation in URL definition. Instead define a
Haskell embedded DSL like happstack's url handling but run it from
template haskell like this:

First define application routes:

module Routes where

import Yesod.Routing

routes =
  routingAlternatives
    [ dir '/' 'Home' // methodGet
    , dir 'entry' 'Entry' // entriesResources
    ]

entriesResources =
  routingAlternatives
    [ placeholder `String 'WithSlug' 'entrySlug' // entryResources
    , dir '/' 'Index' // methodGet
    , dir 'new' 'New' // methodGet
    , dir 'create' 'Create' // methodPost
    ]

entryResources =
  routingAlternatives
    [ dir '/' 'Show' // methodGet
    , dir 'edit' 'Edit' // methodGet
    , dir 'update' 'Update' // methodPut
    , dir '/' 'Destroy' // methodDelete
    ]

now in my application just call this function:

module Main where

import Yesod.Routing
import Routes

$(mkResources 'MyResources' routes)
{- Is the same as

-- data structure name is the second parameter of mkResources
data MyResources =
  -- constructor names are concatenation of dir parameters
    Home
  | EntryShow String
  | EntryEdit String
  | EntryUpdate String
  | EntryDestroy String
  | EntryIndex
  | EntryNew
  | EntryCreate

instance ReadUrl MyResources where ...
instance ShowUrl MyResources where ...
-}

Second wish is to automatically generate datatype for view.

Something like this

$(defineTemplate 'ShowEntryView' [$hamlet|
[$hamlet|
  !!!
  %html
      %head
          %title $templateTitle$
      %body
          %h1 Yesod Sample Blog
          %h2 $templateTitle$
          %ul#nav
              $forall templateNavbar nav
                  %li
                      %a!href=@navUrl.nav@ $navTitle.nav$
          #content
              $templateContent$
  |])
{- is the same like writing

data ShowEntryView =
  ShowEntryView
    { templateTitle :: forall a. HtmlContent a => a
    , templateNavbar :: [ShowEntryViewTemplateNavbar]
    , templateContent :: forall a. HtmlContent a => a
    }

data ShowEntryViewTemplateNavbar =
  ShowEntryViewTemplateNavbar
    { navUrl :: forall a. ShowUrl a => a
    , navTitle :: forall a. HtmlContent a => a
    }

instance HtmlContent ShowEntryView where ...
-}

So template is just a datatype and I just render it in controller method.


More information about the web-devel mailing list