diff --git a/yesod-examples/.gitignore b/yesod-examples/.gitignore
index 47451091..1cd91990 100644
--- a/yesod-examples/.gitignore
+++ b/yesod-examples/.gitignore
@@ -1,2 +1,3 @@
client_session_key.aes
dist
+cabal-dev/
diff --git a/yesod-examples/src/ajax.lhs b/yesod-examples/src/ajax.lhs
index 7bbfaec9..3618204f 100644
--- a/yesod-examples/src/ajax.lhs
+++ b/yesod-examples/src/ajax.lhs
@@ -4,8 +4,9 @@
> {-# LANGUAGE TypeFamilies, QuasiQuotes, TemplateHaskell, MultiParamTypeClasses, OverloadedStrings #-}
> import Yesod
-> import Yesod.Helpers.Static
+> import Yesod.Static
> import Data.Monoid (mempty)
+> import Text.Blaze (string)
Like the blog example, we'll define some data first.
@@ -26,7 +27,6 @@ Like the blog example, we'll define some data first.
> { ajaxPages :: [Page]
> , ajaxStatic :: Static
> }
-> type Handler = GHandler Ajax Ajax
Next we'll generate a function for each file in our static folder. This way, we get a compiler warning when trying to using a file which does not exist.
@@ -34,7 +34,7 @@ Next we'll generate a function for each file in our static folder. This way, we
Now the routes; we'll have a homepage, a pattern for the pages, and use a static subsite for the Javascript and CSS files.
-> mkYesod "Ajax" [$parseRoutes|
+> mkYesod "Ajax" [parseRoutes|
> / HomeR GET
> /page/#String PageR GET
> /static StaticR Static ajaxStatic
@@ -108,5 +108,5 @@ And now the cool part: a handler that returns either HTML or JSON data, dependin
> main :: IO ()
> main = do
> pages <- loadPages
-> let s = static "static/yesod/ajax"
+> s <- static "static/yesod/ajax"
> warpDebug 3000 $ Ajax pages s
diff --git a/yesod-examples/src/blog.lhs b/yesod-examples/src/blog.lhs
index 16ba08b6..65fd2bdd 100644
--- a/yesod-examples/src/blog.lhs
+++ b/yesod-examples/src/blog.lhs
@@ -25,7 +25,6 @@ Since normally you'll need to perform an IO action to load up your entries from
Each Yesod application needs to define the site argument. You can use this for storing anything that should be loaded before running your application. For example, you might store a database connection there. In our case, we'll store our list of entries.
> data Blog = Blog { blogEntries :: [Entry] }
-> type Handler = GHandler Blog Blog
Now we use the first "magical" Yesod set of functions: mkYesod and parseRoutes. If you want to see *exactly* what they do, look at their Haddock docs. For now, we'll try to keep this tutorial simple:
@@ -67,10 +66,9 @@ The Nav datatype will contain navigation information (ie, the URL and title) of
And now the template itself:
-> entryTemplate :: TemplateArgs -> Hamlet (Route Blog)
+> entryTemplate :: TemplateArgs -> HtmlUrl (Route Blog)
> entryTemplate args = [hamlet|
> !!!
->
>
>
> #{templateTitle args}
diff --git a/yesod-examples/src/file-echo.lhs b/yesod-examples/src/file-echo.lhs
index dfbb1299..fc490f83 100644
--- a/yesod-examples/src/file-echo.lhs
+++ b/yesod-examples/src/file-echo.lhs
@@ -4,10 +4,11 @@
> import Data.Monoid (mempty)
> import qualified Data.ByteString.Char8 as S8
> import qualified Data.Text as T
+> import Text.Blaze (string)
> data Echo = Echo
-> mkYesod "Echo" [$parseRoutes|
+> mkYesod "Echo" [parseRoutes|
> / Homepage GET POST
> |]
diff --git a/yesod-examples/src/form.lhs b/yesod-examples/src/form.lhs
index a9d8d14d..57855e51 100644
--- a/yesod-examples/src/form.lhs
+++ b/yesod-examples/src/form.lhs
@@ -7,25 +7,26 @@
> import Data.Text (Text)
> data FormExample = FormExample
-> type Handler = GHandler FormExample FormExample
-> mkYesod "FormExample" [$parseRoutes|
+> mkYesod "FormExample" [parseRoutes|
> / RootR GET
> |]
> instance Yesod FormExample where approot _ = ""
+> instance RenderMessage FormExample FormMessage where
+> renderMessage _ _ = defaultFormMessage
Next, we'll declare a Person datatype with a name and age. After that, we'll create a formlet. A formlet is a declarative approach to forms. It takes a Maybe value and constructs either a blank form, a form based on the original value, or a form based on the values submitted by the user. It also attempts to construct a datatype, failing on validation errors.
> data Person = Person { name :: Text, age :: Int }
> deriving Show
-> personFormlet p = fieldsToTable $ Person
-> <$> stringField "Name" (fmap name p)
-> <*> intField "Age" (fmap age p)
+> personFormlet p = renderTable $ Person
+> <$> areq textField "Name" (fmap name p)
+> <*> areq intField "Age" (fmap age p)
We use an applicative approach and stay mostly declarative. The "fmap name p" bit is just a way to get the name from within a value of type "Maybe Person".
> getRootR :: Handler RepHtml
> getRootR = do
-> (res, wform, enctype) <- runFormGet $ personFormlet Nothing
+> ((res, wform), enctype) <- runFormGet $ personFormlet Nothing
We use runFormGet to bind to GET (query-string) parameters; we could also use runFormPost. The "Nothing" is the initial value of the form. You could also supply a "Just Person" value if you like. There is a three-tuple returned, containing the parsed value, the HTML form as a widget and the encoding type for the form.
diff --git a/yesod-examples/src/generalized-hamlet.lhs b/yesod-examples/src/generalized-hamlet.lhs
index d7a5f490..01d7dc78 100644
--- a/yesod-examples/src/generalized-hamlet.lhs
+++ b/yesod-examples/src/generalized-hamlet.lhs
@@ -4,7 +4,7 @@ Yesod has instances for:
* Html
-* Hamlet url (= (url -> [(String, String)] -> String) -> Html)
+* HtmlUrl (= (url -> [(String, String)] -> String) -> Html)
* GWidget s m ()
@@ -13,15 +13,15 @@ your own instances.
> {-# LANGUAGE QuasiQuotes, TypeFamilies, MultiParamTypeClasses, OverloadedStrings, TemplateHaskell #-}
> import Yesod
+> import Text.Hamlet (shamlet)
> data NewHamlet = NewHamlet
> mkYesod "NewHamlet" [$parseRoutes|/ RootR GET|]
> instance Yesod NewHamlet where approot _ = ""
-> type Widget = GWidget NewHamlet NewHamlet
>
> myHtml :: Html
-> myHtml = [$hamlet|
Just don't use any URLs in here!|]
+> myHtml = [shamlet|
Just don't use any URLs in here!|]
>
-> myInnerWidget :: Widget ()
+> myInnerWidget :: Widget
> myInnerWidget = do
> addHamlet [$hamlet|
>