Skip to content

Instantly share code, notes, and snippets.

@softmechanics
Created January 19, 2011 09:11
Show Gist options
  • Save softmechanics/785897 to your computer and use it in GitHub Desktop.
Save softmechanics/785897 to your computer and use it in GitHub Desktop.
{-# LANGUAGE QuasiQuotes
, TemplateHaskell
, OverloadedStrings
, TypeFamilies
#-}
import Yesod
import Yesod.Form
import Yesod.Form.Jquery
import Control.Applicative
import Data.Time
data Test = Test
instance YesodJquery Test
data Params = Params
{ dateTime :: UTCTime
}
deriving (Show)
paramsFormlet :: YesodJquery m => Maybe Params -> Form s m Params
paramsFormlet mparams = fieldsToTable $ Params
<$> jqueryDayTimeField "Date and Time" (fmap dateTime mparams)
getRootR :: GHandler Test Test RepHtml
getRootR = do
(res,w,enc) <- runFormGet $ paramsFormlet Nothing
defaultLayout $ do
[$hamlet|
$show res$
%form!enctype=$enc$!method=GET
%table
^w^
%tr
%td!colspan=2
%input!type=submit
|]
mkYesod "Test" [$parseRoutes|
/ RootR GET
|]
instance Yesod Test where approot _ = ""
main = warp 3000 Test
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment