-- | -- Module: Yesod.TableView.NumEntriesForm -- Copyright: (c) 2010 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- Stability: experimental -- -- Little form for selecting the number of entries to show. {-# LANGUAGE TemplateHaskell #-} module Yesod.TableView.NumEntriesForm ( runNumEntriesForm ) where import Control.Arrow import Control.Monad import Data.String import Text.Cassius import Text.Hamlet import Yesod numEntriesForm :: String -> [Int] -> FormletField sub s Int numEntriesForm prompt options mdata = let numbers = map (id &&& show) options in selectField numbers (fromString prompt) mdata -- | Run the number of entries form with the given prompt, options, -- initial value and route function. If POST data is present, redirects -- to the given route with the specified limit, otherwise just returns -- the form widget. runNumEntriesForm :: Bool -> String -> [Int] -> Int -> (Int -> Route s) -> GHandler sub s (GWidget sub s ()) runNumEntriesForm styled prompt options limit thisRoute = do let formField = numEntriesForm prompt options (Just limit) (res, form) <- runFormDivs (thisRoute limit) "Ok" formField case res of FormSuccess newLimit -> redirect RedirectTemporary (thisRoute newLimit) _ -> return $ do when styled $ addCassius $(cassiusFile "templates/form-numentries.cassius") addWidget $(hamletFile "templates/form-numentries.hamlet")