[Haskell-cafe] Yesod Problem - passing values inside a route
Michael Snoyman
michael at snoyman.com
Sun May 28 13:12:44 UTC 2017
I'm on mobile now, but you want to use the ^?{} syntax which allows you to
pass a pair of route and query string parameters. There's an example in the
Shakespeare chapter of the book.
On Sat, May 27, 2017, 8:34 AM Michael Litchard <litchard.michael at gmail.com>
wrote:
> Below I have an example from the Yesod
> <https://www.yesodweb.com/book/forms> book. The form action maps to a
> route. How do I pass a value to that route. I know it has something to do
> with ^ but I can't see to make it work right.
>
> {-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE OverloadedStrings #-}{-# LANGUAGE QuasiQuotes #-}{-# LANGUAGE TemplateHaskell #-}{-# LANGUAGE TypeFamilies #-}import Control.Applicativeimport Data.Text (Text)import Yesod
> data App = App
>
> mkYesod "App" [parseRoutes|/ HomeR GET/input InputR GET|]
>
> instance Yesod App
>
> instance RenderMessage App FormMessage where
> renderMessage _ _ = defaultFormMessage
> data Person = Person
> { personName :: Text
> , personAge :: Int
> }
> deriving Show
>
> getHomeR :: Handler Html
> getHomeR = defaultLayout
> [whamlet|
> <form action=@{InputR}> <--- problem line -- want to do this <form action=@{InputR ^haskellValue}>
> <p>
> My name is
> <input type=text name=name>
> and I am
> <input type=text name=age>
> years old.
> <input type=submit value="Introduce myself">
> |]
>
> getInputR :: Text -> Handler Html
> getInputR label = do
> person <- runInputGet $ Person
> <$> ireq textField label
> <*> ireq intField "age"
> defaultLayout [whamlet|<p>#{show person}|]
>
> main :: IO ()
> main = warp 3000 App
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170528/af557ab8/attachment.html>
More information about the Haskell-Cafe
mailing list