Skip to content

Instantly share code, notes, and snippets.

@snoyberg
Created October 11, 2012 07:46
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save snoyberg/3870834 to your computer and use it in GitHub Desktop.
Save snoyberg/3870834 to your computer and use it in GitHub Desktop.
Demonstrate conversion from standard Yesod to yesod-pure
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
import Text.Blaze.Html (toValue, (!))
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as HA
import Yesod.Pure
data App = App
mkYesod "App" [parseRoutes|
/ HomeR GET
/fib/#Int FibR GET
|]
instance Yesod App
getHomeR :: Handler RepHtml
getHomeR = defaultLayout $ do
setTitle "Hello World!"
toWidget $ \render -> do
H.p "Hello World"
H.a ! HA.href (toValue $ render (FibR 5) []) $ "Fifth fib"
addCSS "p { color: red }"
getFibR :: Int -> Handler RepHtml
getFibR i = defaultLayout $ do
setTitle "Fibs"
toWidget $ \render -> do
H.p $ do
"Fib for "
toHtml i
": "
toHtml $ fibs !! i
H.a ! HA.href (toValue $ render (FibR $ i + 1) []) $ "Next fib"
fib :: Int -> Int
fib i = fibs !! i
fibs :: [Int]
fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
main :: IO ()
main = warpDebug 3000 App
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment