{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE CPP #-} module Yesod.Form.Fields ( -- * Fields -- ** Required stringField , passwordField , textareaField , hiddenField , intField , doubleField , dayField , timeField , htmlField , selectField , radioField , boolField , emailField , searchField , urlField , fileField -- ** Optional , maybeStringField , maybePasswordField , maybeTextareaField , maybeHiddenField , maybeIntField , maybeDoubleField , maybeDayField , maybeTimeField , maybeHtmlField , maybeSelectField , maybeRadioField , maybeEmailField , maybeSearchField , maybeUrlField , maybeFileField -- * Inputs -- ** Required , stringInput , intInput , boolInput , dayInput , emailInput , urlInput -- ** Optional , maybeStringInput , maybeDayInput , maybeIntInput ) where import Yesod.Form.Core import Yesod.Form.Profiles import Yesod.Request (FileInfo) import Yesod.Widget (GWidget) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Reader (ask) import Data.Time (Day, TimeOfDay) import Text.Hamlet import Data.Monoid import Control.Monad (join) import Data.Maybe (fromMaybe, isNothing) #if __GLASGOW_HASKELL__ >= 700 #define HAMLET hamlet #else #define HAMLET $hamlet #endif stringField :: (IsForm f, FormType f ~ String) => FormFieldSettings -> Maybe String -> f stringField = requiredFieldHelper stringFieldProfile maybeStringField :: (IsForm f, FormType f ~ Maybe String) => FormFieldSettings -> Maybe (Maybe String) -> f maybeStringField = optionalFieldHelper stringFieldProfile passwordField :: (IsForm f, FormType f ~ String) => FormFieldSettings -> Maybe String -> f passwordField = requiredFieldHelper passwordFieldProfile maybePasswordField :: (IsForm f, FormType f ~ Maybe String) => FormFieldSettings -> Maybe (Maybe String) -> f maybePasswordField = optionalFieldHelper passwordFieldProfile intInput :: Integral i => String -> FormInput sub master i intInput n = mapFormXml fieldsToInput $ requiredFieldHelper intFieldProfile (nameSettings n) Nothing maybeIntInput :: Integral i => String -> FormInput sub master (Maybe i) maybeIntInput n = mapFormXml fieldsToInput $ optionalFieldHelper intFieldProfile (nameSettings n) Nothing intField :: (Integral (FormType f), IsForm f) => FormFieldSettings -> Maybe (FormType f) -> f intField = requiredFieldHelper intFieldProfile maybeIntField :: (Integral i, FormType f ~ Maybe i, IsForm f) => FormFieldSettings -> Maybe (FormType f) -> f maybeIntField = optionalFieldHelper intFieldProfile doubleField :: (IsForm f, FormType f ~ Double) => FormFieldSettings -> Maybe Double -> f doubleField = requiredFieldHelper doubleFieldProfile maybeDoubleField :: (IsForm f, FormType f ~ Maybe Double) => FormFieldSettings -> Maybe (Maybe Double) -> f maybeDoubleField = optionalFieldHelper doubleFieldProfile dayField :: (IsForm f, FormType f ~ Day) => FormFieldSettings -> Maybe Day -> f dayField = requiredFieldHelper dayFieldProfile maybeDayField :: (IsForm f, FormType f ~ Maybe Day) => FormFieldSettings -> Maybe (Maybe Day) -> f maybeDayField = optionalFieldHelper dayFieldProfile timeField :: (IsForm f, FormType f ~ TimeOfDay) => FormFieldSettings -> Maybe TimeOfDay -> f timeField = requiredFieldHelper timeFieldProfile maybeTimeField :: (IsForm f, FormType f ~ Maybe TimeOfDay) => FormFieldSettings -> Maybe (Maybe TimeOfDay) -> f maybeTimeField = optionalFieldHelper timeFieldProfile boolField :: (IsForm f, FormType f ~ Bool) => FormFieldSettings -> Maybe Bool -> f boolField ffs orig = toForm $ do env <- askParams let label = ffsLabel ffs tooltip = ffsTooltip ffs name <- maybe newFormIdent return $ ffsName ffs theId <- maybe newFormIdent return $ ffsId ffs let (res, val) = if null env then (FormMissing, fromMaybe False orig) else case lookup name env of Nothing -> (FormSuccess False, False) Just "" -> (FormSuccess False, False) Just "false" -> (FormSuccess False, False) Just _ -> (FormSuccess True, True) let fi = FieldInfo { fiLabel = string label , fiTooltip = tooltip , fiIdent = theId , fiInput = [HAMLET| |] , fiErrors = case res of FormFailure [x] -> Just $ string x _ -> Nothing , fiRequired = True } return (res, fi, UrlEncoded) htmlField :: (IsForm f, FormType f ~ Html) => FormFieldSettings -> Maybe Html -> f htmlField = requiredFieldHelper htmlFieldProfile maybeHtmlField :: (IsForm f, FormType f ~ Maybe Html) => FormFieldSettings -> Maybe (Maybe Html) -> f maybeHtmlField = optionalFieldHelper htmlFieldProfile selectField :: (Eq x, IsForm f, FormType f ~ x) => [(x, String)] -> FormFieldSettings -> Maybe x -> f selectField pairs ffs initial = toForm $ do env <- askParams let label = ffsLabel ffs tooltip = ffsTooltip ffs theId <- maybe newFormIdent return $ ffsId ffs name <- maybe newFormIdent return $ ffsName ffs let pairs' = zip [1 :: Int ..] pairs let res = case lookup name env of Nothing -> FormMissing Just "none" -> FormFailure ["Field is required"] Just x -> case reads x of (x', _):_ -> case lookup x' pairs' of Nothing -> FormFailure ["Invalid entry"] Just (y, _) -> FormSuccess y [] -> FormFailure ["Invalid entry"] let isSelected x = case res of FormSuccess y -> x == y _ -> Just x == initial let input = #if __GLASGOW_HASKELL__ >= 700 [hamlet| #else [$hamlet| #endif