[Haskell-beginners] Yesod question - ajax.lhs
Michael Snoyman
michael at snoyman.com
Fri May 20 05:38:40 CEST 2011
On Fri, May 20, 2011 at 3:38 AM, Michael Litchard <michael at schmong.org> wrote:
> I'm using yesod 0.8.1
>
> I'm playing around with yesod examples 0.8.0.1 and I noticed a few
> things that send up some red flags
>
> first thing, when I try to run ajax.lhs from the top level directory
>
>
>
>
> src/ajax.lhs:6:3:
> Warning: In the use of `string'
> (imported from Yesod, but defined in Text.Blaze.Internal):
> Deprecated: "Use Blaze.Html.toHtml"
This is just using an older version of blaze-html. Replacing "string"
with "toHtml" should work just fine.
> src/ajax.lhs:37:18:
> Warning: Deprecated syntax:
> quasiquotes no longer need a dollar sign: $parseRoutes
>
> src/ajax.lhs:52:21:
> Warning: Deprecated syntax:
> quasiquotes no longer need a dollar sign: $hamlet
>
> src/ajax.lhs:93:17:
> Warning: Deprecated syntax:
> quasiquotes no longer need a dollar sign: $hamlet
This is intentional. GHC 7 changed the syntax for QQ. The examples
still mostly use the GHC 6.12 syntax for backwards compatibility.
>
> This is suggesting to me the example code hasn't caught up to the
> changes in yesod, which can cause confusion for n00bs like me.
>
> I'm trying to learn how to use jQuery via yesod, and when I see the
> html generated from the current ajax.lhs this is what comes up
>
> <!DOCTYPE html><html><head><title>Page 1</title><link rel="stylesheet"
> href="/static/style%2Ecss?YaQxW21D"><script
> src="http://ajax.googleapis.com/ajax/libs/jquery/1.4.2/jquery.min.js"></script><script
> src="/static/script%2Ejs?NWBIzSLG"></script></head><body><ul
> id="navbar"><li><a href="/page/page%2D1">Page 1</a></li><li><a
> href="/page/page%2D2">Page 2</a></li><li><a href="/page/page%2D3">Page
> 3</a></li></ul><div id="content"><h1>Page 1</h1><article>My first
> page</article></div></body></html>
>
> I want to draw attention to
> <script src="/static/script%2Ejs?NWBIzSLG"> and things like this. This
> is the other red flag that the example code hasn't caught up to the
> current state of Yesod. Am I interpreting the problem correctly?
Yesod provides the query string as an optimization to allow you to set
cache headers. There's a good reason the code looks like that. (Though
I'm surprised the period is getting URL-encoded, looks like an issue
with http-types. And before anyone bugs the author of the package, it
looks like an issue with the code *I* wrote.)
> Here is what the latest example of ajax.lhs looks like. Could someone
> tell me what needs to change to prevent the above problems from
> happening?
>
>> {-# LANGUAGE TypeFamilies, QuasiQuotes, TemplateHaskell, MultiParamTypeClasses, OverloadedStrings #-}
>> import Yesod
>> import Yesod.Helpers.Static
>> import Data.Monoid (mempty)
>
> Like the blog example, we'll define some data first.
>
>> data Page = Page
>> { pageName :: String
>> , pageSlug :: String
>> , pageContent :: String
>> }
>
>> loadPages :: IO [Page]
>> loadPages = return
>> [ Page "Page 1" "page-1" "My first page"
>> , Page "Page 2" "page-2" "My second page"
>> , Page "Page 3" "page-3" "My third page"
>> ]
>
>> data Ajax = Ajax
>> { ajaxPages :: [Page]
>> , ajaxStatic :: Static
>> }
>> type Handler = GHandler Ajax Ajax
>
>
>> staticFiles "static/yesod/ajax"
>
>> mkYesod "Ajax" [$parseRoutes|
>> / HomeR GET
>> /page/#String PageR GET
>> /static StaticR Static ajaxStatic
>> |]
>
>
>> instance Yesod Ajax where
>> approot _ = ""
>> defaultLayout widget = do
>> Ajax pages _ <- getYesod
>> content <- widgetToPageContent widget
>> hamletToRepHtml [$hamlet|
>> \<!DOCTYPE html>
>>
>> <html>
>> <head>
>> <title>#{pageTitle content}
>> <link rel="stylesheet" href="@{StaticR style_css}">
>> <script src="http://ajax.googleapis.com/ajax/libs/jquery/1.4.2/jquery.min.js">
>> <script src="@{StaticR script_js}">
>> \^{pageHead content}
>> <body>
>> <ul id="navbar">
>> $forall page <- pages
>> <li>
>> <a href="@{PageR (pageSlug page)}">#{pageName page}
>> <div id="content">
>> \^{pageBody content}
>> |]
>
>
>> getHomeR :: Handler ()
>> getHomeR = do
>> Ajax pages _ <- getYesod
>> let first = head pages
>> redirect RedirectTemporary $ PageR $ pageSlug first
>
>> getPageR :: String -> Handler RepHtmlJson
>> getPageR slug = do
>> Ajax pages _ <- getYesod
>> case filter (\e -> pageSlug e == slug) pages of
>> [] -> notFound
>> page:_ -> defaultLayoutJson (do
>> setTitle $ string $ pageName page
>> addHamlet $ html page
>> ) (json page)
>> where
>> html page = [$hamlet|
>> <h1>#{pageName page}
>> <article>#{pageContent page}
>> |]
>> json page = jsonMap
>> [ ("name", jsonScalar $ pageName page)
>> , ("content", jsonScalar $ pageContent page)
>> ]
>
>> main :: IO ()
>> main = do
>> pages <- loadPages
>> let s = static "static/yesod/ajax"
>> warpDebug 3000 $ Ajax pages s
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
More information about the Beginners
mailing list