{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE CPP #-} -- | Field functions allow you to easily create and validate forms, cleanly handling the uncertainty of parsing user input. -- -- When possible, the field functions use a specific input type (e.g. "number"), allowing supporting browsers to validate the input before form submission. Browsers can also improve usability with this information; for example, mobile browsers might present a specialized keyboard for an input of type "email" or "number". -- -- See the Yesod book for a broader overview of forms in Yesod. module Yesod.Form.Fields ( -- * i18n FormMessage (..) , defaultFormMessage -- * Fields , textField , passwordField , textareaField , hiddenField , intField , dayField , timeField , timeFieldTypeTime , timeFieldTypeText , htmlField , emailField , multiEmailField , searchField , AutoFocus , urlField , doubleField , parseDate , parseTime , Textarea (..) , boolField , checkBoxField , fileField -- * File 'AForm's , fileAFormReq , fileAFormOpt -- * Options -- $optionsOverview , selectFieldHelper , selectField , selectFieldList , selectFieldListGrouped , radioField , radioFieldList , checkboxesField , checkboxesFieldList , multiSelectField , multiSelectFieldList , Option (..) , OptionList (..) , mkOptionList , mkOptionListGrouped , optionsPersist , optionsPersistKey , optionsPairs , optionsPairsGrouped , optionsEnum ) where import Yesod.Form.Types import Yesod.Form.I18n.English import Yesod.Form.Functions (parseHelper) import Yesod.Core import Text.Blaze (ToMarkup (toMarkup), unsafeByteString) #define ToHtml ToMarkup #define toHtml toMarkup #define preEscapedText preEscapedToMarkup import Data.Time (Day, TimeOfDay(..)) import qualified Text.Email.Validate as Email import Data.Text.Encoding (encodeUtf8, decodeUtf8With) import Data.Text.Encoding.Error (lenientDecode) import Network.URI (parseURI) import Database.Persist.Sql (PersistField, PersistFieldSql (..)) #if MIN_VERSION_persistent(2,5,0) import Database.Persist (Entity (..), SqlType (SqlString), PersistRecordBackend, PersistQueryRead) #else import Database.Persist (Entity (..), SqlType (SqlString), PersistEntity, PersistQuery, PersistEntityBackend) #endif import Text.HTML.SanitizeXSS (sanitizeBalance) import Control.Monad (when, unless, forM_) import Data.Either (partitionEithers) import Data.Maybe (listToMaybe, fromMaybe) import qualified Blaze.ByteString.Builder.Html.Utf8 as B import Blaze.ByteString.Builder (writeByteString, toLazyByteString) import Blaze.ByteString.Builder.Internal.Write (fromWriteList) import Text.Blaze.Html.Renderer.String (renderHtml) import qualified Data.ByteString as S import qualified Data.ByteString.Lazy as L import Data.Text as T ( Text, append, concat, cons, head , intercalate, isPrefixOf, null, unpack, pack, splitOn ) import qualified Data.Text as T (drop, dropWhile) import qualified Data.Text.Read import qualified Data.Map as Map import Yesod.Persist (selectList, Filter, SelectOpt, Key) import Control.Arrow ((&&&)) import Control.Applicative ((<$>), (<|>)) import Data.Attoparsec.Text (Parser, char, string, digit, skipSpace, endOfInput, parseOnly) import Yesod.Persist.Core import Data.String (IsString) #if !MIN_VERSION_base(4,8,0) import Data.Monoid #endif defaultFormMessage :: FormMessage -> Text defaultFormMessage = englishFormMessage -- | Creates a input with @type="number"@ and @step=1@. intField :: (Monad m, Integral i, RenderMessage (HandlerSite m) FormMessage) => Field m i intField = Field { fieldParse = parseHelper $ \s -> case Data.Text.Read.signed Data.Text.Read.decimal s of Right (a, "") -> Right a _ -> Left $ MsgInvalidInteger s , fieldView = \theId name attrs val isReq -> toWidget [hamlet| $newline never |] , fieldEnctype = UrlEncoded } where showVal = either id (pack . showI) showI x = show (fromIntegral x :: Integer) -- | Creates a input with @type="number"@ and @step=any@. doubleField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Double doubleField = Field { fieldParse = parseHelper $ \s -> case Data.Text.Read.double (prependZero s) of Right (a, "") -> Right a _ -> Left $ MsgInvalidNumber s , fieldView = \theId name attrs val isReq -> toWidget [hamlet| $newline never |] , fieldEnctype = UrlEncoded } where showVal = either id (pack . show) -- | Creates an input with @type="date"@, validating the input using the 'parseDate' function. -- -- Add the @time@ package and import the "Data.Time.Calendar" module to use this function. dayField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Day dayField = Field { fieldParse = parseHelper $ parseDate . unpack , fieldView = \theId name attrs val isReq -> toWidget [hamlet| $newline never |] , fieldEnctype = UrlEncoded } where showVal = either id (pack . show) -- | An alias for 'timeFieldTypeTime'. timeField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay timeField = timeFieldTypeTime -- | Creates an input with @type="time"@. will fallback to a text field, and Yesod will parse the time as described in 'timeFieldTypeText'. -- -- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function. -- -- @since 1.4.2 timeFieldTypeTime :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay timeFieldTypeTime = timeFieldOfType "time" -- | Creates an input with @type="text"@, parsing the time from an [H]H:MM[:SS] format, with an optional AM or PM (if not given, AM is assumed for compatibility with the 24 hour clock system). -- -- This function exists for backwards compatibility with the old implementation of 'timeField', which used to use @type="text"@. Consider using 'timeField' or 'timeFieldTypeTime' for improved UX and validation from the browser. -- -- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function. -- -- @since 1.4.2 timeFieldTypeText :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay timeFieldTypeText = timeFieldOfType "text" timeFieldOfType :: Monad m => RenderMessage (HandlerSite m) FormMessage => Text -> Field m TimeOfDay timeFieldOfType inputType = Field { fieldParse = parseHelper parseTime , fieldView = \theId name attrs val isReq -> toWidget [hamlet| $newline never |] , fieldEnctype = UrlEncoded } where showVal = either id (pack . show . roundFullSeconds) roundFullSeconds tod = TimeOfDay (todHour tod) (todMin tod) fullSec where fullSec = fromInteger $ floor $ todSec tod -- | Creates a @\