Fields.hs 34 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866
  1. {-# LANGUAGE ConstraintKinds #-}
  2. {-# LANGUAGE QuasiQuotes #-}
  3. {-# LANGUAGE TypeFamilies #-}
  4. {-# LANGUAGE OverloadedStrings #-}
  5. {-# LANGUAGE GeneralizedNewtypeDeriving #-}
  6. {-# LANGUAGE FlexibleContexts #-}
  7. {-# LANGUAGE CPP #-}
  8. -- | Field functions allow you to easily create and validate forms, cleanly handling the uncertainty of parsing user input.
  9. --
  10. -- 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".
  11. --
  12. -- See the Yesod book <http://www.yesodweb.com/book/forms chapter on forms> for a broader overview of forms in Yesod.
  13. module Yesod.Form.Fields
  14. ( -- * i18n
  15. FormMessage (..)
  16. , defaultFormMessage
  17. -- * Fields
  18. , textField
  19. , passwordField
  20. , textareaField
  21. , hiddenField
  22. , intField
  23. , dayField
  24. , timeField
  25. , timeFieldTypeTime
  26. , timeFieldTypeText
  27. , htmlField
  28. , emailField
  29. , multiEmailField
  30. , searchField
  31. , AutoFocus
  32. , urlField
  33. , doubleField
  34. , parseDate
  35. , parseTime
  36. , Textarea (..)
  37. , boolField
  38. , checkBoxField
  39. , fileField
  40. -- * File 'AForm's
  41. , fileAFormReq
  42. , fileAFormOpt
  43. -- * Options
  44. -- $optionsOverview
  45. , selectField
  46. , selectFieldList
  47. , radioField
  48. , radioFieldList
  49. , checkboxesField
  50. , checkboxesFieldList
  51. , multiSelectField
  52. , multiSelectFieldList
  53. , Option (..)
  54. , OptionList (..)
  55. , mkOptionList
  56. , optionsPersist
  57. , optionsPersistKey
  58. , optionsPairs
  59. , optionsEnum
  60. ) where
  61. import Yesod.Form.Types
  62. import Yesod.Form.I18n.English
  63. import Yesod.Form.Functions (parseHelper)
  64. import Yesod.Core
  65. import Text.Hamlet
  66. import Text.Blaze (ToMarkup (toMarkup), unsafeByteString)
  67. #define ToHtml ToMarkup
  68. #define toHtml toMarkup
  69. #define preEscapedText preEscapedToMarkup
  70. import Text.Cassius
  71. import Data.Time (Day, TimeOfDay(..))
  72. import qualified Text.Email.Validate as Email
  73. import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
  74. import Data.Text.Encoding.Error (lenientDecode)
  75. import Network.URI (parseURI)
  76. import Database.Persist.Sql (PersistField, PersistFieldSql (..))
  77. #if MIN_VERSION_persistent(2,5,0)
  78. import Database.Persist (Entity (..), SqlType (SqlString), PersistRecordBackend, PersistQueryRead)
  79. #else
  80. import Database.Persist (Entity (..), SqlType (SqlString))
  81. #endif
  82. import Text.HTML.SanitizeXSS (sanitizeBalance)
  83. import Control.Monad (when, unless)
  84. import Data.Either (partitionEithers)
  85. import Data.Maybe (listToMaybe, fromMaybe)
  86. import qualified Blaze.ByteString.Builder.Html.Utf8 as B
  87. import Blaze.ByteString.Builder (writeByteString, toLazyByteString)
  88. import Blaze.ByteString.Builder.Internal.Write (fromWriteList)
  89. import Database.Persist (PersistEntityBackend)
  90. import Text.Blaze.Html.Renderer.String (renderHtml)
  91. import qualified Data.ByteString as S
  92. import qualified Data.ByteString.Lazy as L
  93. import Data.Text as T ( Text, append, concat, cons, head
  94. , intercalate, isPrefixOf, null, unpack, pack, splitOn
  95. )
  96. import qualified Data.Text as T (drop, dropWhile)
  97. import qualified Data.Text.Read
  98. import qualified Data.Map as Map
  99. import Yesod.Persist (selectList, runDB, Filter, SelectOpt, Key, YesodPersist, PersistEntity, PersistQuery)
  100. import Control.Arrow ((&&&))
  101. import Control.Applicative ((<$>), (<|>))
  102. import Data.Attoparsec.Text (Parser, char, string, digit, skipSpace, endOfInput, parseOnly)
  103. import Yesod.Persist.Core
  104. defaultFormMessage :: FormMessage -> Text
  105. defaultFormMessage = englishFormMessage
  106. -- | Creates a input with @type="number"@ and @step=1@.
  107. intField :: (Monad m, Integral i, RenderMessage (HandlerSite m) FormMessage) => Field m i
  108. intField = Field
  109. { fieldParse = parseHelper $ \s ->
  110. case Data.Text.Read.signed Data.Text.Read.decimal s of
  111. Right (a, "") -> Right a
  112. _ -> Left $ MsgInvalidInteger s
  113. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  114. $newline never
  115. <input id="#{theId}" name="#{name}" *{attrs} type="number" step=1 :isReq:required="" value="#{showVal val}">
  116. |]
  117. , fieldEnctype = UrlEncoded
  118. }
  119. where
  120. showVal = either id (pack . showI)
  121. showI x = show (fromIntegral x :: Integer)
  122. -- | Creates a input with @type="number"@ and @step=any@.
  123. doubleField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Double
  124. doubleField = Field
  125. { fieldParse = parseHelper $ \s ->
  126. case Data.Text.Read.double (prependZero s) of
  127. Right (a, "") -> Right a
  128. _ -> Left $ MsgInvalidNumber s
  129. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  130. $newline never
  131. <input id="#{theId}" name="#{name}" *{attrs} type="number" step=any :isReq:required="" value="#{showVal val}">
  132. |]
  133. , fieldEnctype = UrlEncoded
  134. }
  135. where showVal = either id (pack . show)
  136. -- | Creates an input with @type="date"@, validating the input using the 'parseDate' function.
  137. --
  138. -- Add the @time@ package and import the "Data.Time.Calendar" module to use this function.
  139. dayField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Day
  140. dayField = Field
  141. { fieldParse = parseHelper $ parseDate . unpack
  142. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  143. $newline never
  144. <input id="#{theId}" name="#{name}" *{attrs} type="date" :isReq:required="" value="#{showVal val}">
  145. |]
  146. , fieldEnctype = UrlEncoded
  147. }
  148. where showVal = either id (pack . show)
  149. -- | An alias for 'timeFieldTypeText'.
  150. timeField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay
  151. timeField = timeFieldTypeText
  152. {-# DEPRECATED timeField "'timeField' currently defaults to an input of type=\"text\". In the next major release, it will default to type=\"time\". To opt in to the new functionality, use 'timeFieldTypeTime'. To keep the existing behavior, use 'timeFieldTypeText'. See 'https://github.com/yesodweb/yesod/pull/874' for details." #-}
  153. -- | Creates an input with @type="time"@. <http://caniuse.com/#search=time%20input%20type Browsers not supporting this type> will fallback to a text field, and Yesod will parse the time as described in 'timeFieldTypeText'.
  154. --
  155. -- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function.
  156. --
  157. -- Since 1.4.2
  158. timeFieldTypeTime :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay
  159. timeFieldTypeTime = timeFieldOfType "time"
  160. -- | 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).
  161. --
  162. -- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function.
  163. --
  164. -- Since 1.4.2
  165. timeFieldTypeText :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay
  166. timeFieldTypeText = timeFieldOfType "text"
  167. timeFieldOfType :: Monad m => RenderMessage (HandlerSite m) FormMessage => Text -> Field m TimeOfDay
  168. timeFieldOfType inputType = Field
  169. { fieldParse = parseHelper parseTime
  170. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  171. $newline never
  172. <input id="#{theId}" name="#{name}" *{attrs} type="#{inputType}" :isReq:required="" value="#{showVal val}">
  173. |]
  174. , fieldEnctype = UrlEncoded
  175. }
  176. where
  177. showVal = either id (pack . show . roundFullSeconds)
  178. roundFullSeconds tod =
  179. TimeOfDay (todHour tod) (todMin tod) fullSec
  180. where
  181. fullSec = fromInteger $ floor $ todSec tod
  182. -- | Creates a @\<textarea>@ tag whose input is sanitized to prevent XSS attacks and is validated for having balanced tags.
  183. htmlField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Html
  184. htmlField = Field
  185. { fieldParse = parseHelper $ Right . preEscapedText . sanitizeBalance
  186. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  187. $newline never
  188. <textarea :isReq:required="" id="#{theId}" name="#{name}" *{attrs}>#{showVal val}
  189. |]
  190. , fieldEnctype = UrlEncoded
  191. }
  192. where showVal = either id (pack . renderHtml)
  193. -- | A newtype wrapper around a 'Text' whose 'ToMarkup' instance converts newlines to HTML @\<br>@ tags.
  194. --
  195. -- (When text is entered into a @\<textarea>@, newline characters are used to separate lines.
  196. -- If this text is then placed verbatim into HTML, the lines won't be separated, thus the need for replacing with @\<br>@ tags).
  197. -- If you don't need this functionality, simply use 'unTextarea' to access the raw text.
  198. newtype Textarea = Textarea { unTextarea :: Text }
  199. deriving (Show, Read, Eq, PersistField, Ord, ToJSON, FromJSON)
  200. instance PersistFieldSql Textarea where
  201. sqlType _ = SqlString
  202. instance ToHtml Textarea where
  203. toHtml =
  204. unsafeByteString
  205. . S.concat
  206. . L.toChunks
  207. . toLazyByteString
  208. . fromWriteList writeHtmlEscapedChar
  209. . unpack
  210. . unTextarea
  211. where
  212. -- Taken from blaze-builder and modified with newline handling.
  213. writeHtmlEscapedChar '\n' = writeByteString "<br>"
  214. writeHtmlEscapedChar c = B.writeHtmlEscapedChar c
  215. -- | Creates a @\<textarea>@ tag whose returned value is wrapped in a 'Textarea'; see 'Textarea' for details.
  216. textareaField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Textarea
  217. textareaField = Field
  218. { fieldParse = parseHelper $ Right . Textarea
  219. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  220. $newline never
  221. <textarea id="#{theId}" name="#{name}" :isReq:required="" *{attrs}>#{either id unTextarea val}
  222. |]
  223. , fieldEnctype = UrlEncoded
  224. }
  225. -- | Creates an input with @type="hidden"@; you can use this to store information in a form that users shouldn't see (for example, Yesod stores CSRF tokens in a hidden field).
  226. hiddenField :: (Monad m, PathPiece p, RenderMessage (HandlerSite m) FormMessage)
  227. => Field m p
  228. hiddenField = Field
  229. { fieldParse = parseHelper $ maybe (Left MsgValueRequired) Right . fromPathPiece
  230. , fieldView = \theId name attrs val _isReq -> toWidget [hamlet|
  231. $newline never
  232. <input type="hidden" id="#{theId}" name="#{name}" *{attrs} value="#{either id toPathPiece val}">
  233. |]
  234. , fieldEnctype = UrlEncoded
  235. }
  236. -- | Creates a input with @type="text"@.
  237. textField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Text
  238. textField = Field
  239. { fieldParse = parseHelper $ Right
  240. , fieldView = \theId name attrs val isReq ->
  241. [whamlet|
  242. $newline never
  243. <input id="#{theId}" name="#{name}" *{attrs} type="text" :isReq:required value="#{either id id val}">
  244. |]
  245. , fieldEnctype = UrlEncoded
  246. }
  247. -- | Creates an input with @type="password"@.
  248. passwordField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Text
  249. passwordField = Field
  250. { fieldParse = parseHelper $ Right
  251. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  252. $newline never
  253. <input id="#{theId}" name="#{name}" *{attrs} type="password" :isReq:required="" value="#{either id id val}">
  254. |]
  255. , fieldEnctype = UrlEncoded
  256. }
  257. readMay :: Read a => String -> Maybe a
  258. readMay s = case filter (Prelude.null . snd) $ reads s of
  259. (x, _):_ -> Just x
  260. [] -> Nothing
  261. -- | Parses a 'Day' from a 'String'.
  262. parseDate :: String -> Either FormMessage Day
  263. parseDate = maybe (Left MsgInvalidDay) Right
  264. . readMay . replace '/' '-'
  265. -- | Replaces all instances of a value in a list by another value.
  266. -- from http://hackage.haskell.org/packages/archive/cgi/3001.1.7.1/doc/html/src/Network-CGI-Protocol.html#replace
  267. replace :: Eq a => a -> a -> [a] -> [a]
  268. replace x y = map (\z -> if z == x then y else z)
  269. parseTime :: Text -> Either FormMessage TimeOfDay
  270. parseTime = either (Left . fromMaybe MsgInvalidTimeFormat . readMay . drop 2 . dropWhile (/= ':')) Right . parseOnly timeParser
  271. timeParser :: Parser TimeOfDay
  272. timeParser = do
  273. skipSpace
  274. h <- hour
  275. _ <- char ':'
  276. m <- minsec MsgInvalidMinute
  277. hasSec <- (char ':' >> return True) <|> return False
  278. s <- if hasSec then minsec MsgInvalidSecond else return 0
  279. skipSpace
  280. isPM <-
  281. (string "am" >> return (Just False)) <|>
  282. (string "AM" >> return (Just False)) <|>
  283. (string "pm" >> return (Just True)) <|>
  284. (string "PM" >> return (Just True)) <|>
  285. return Nothing
  286. h' <-
  287. case isPM of
  288. Nothing -> return h
  289. Just x
  290. | h <= 0 || h > 12 -> fail $ show $ MsgInvalidHour $ pack $ show h
  291. | h == 12 -> return $ if x then 12 else 0
  292. | otherwise -> return $ h + (if x then 12 else 0)
  293. skipSpace
  294. endOfInput
  295. return $ TimeOfDay h' m s
  296. where
  297. hour = do
  298. x <- digit
  299. y <- (return <$> digit) <|> return []
  300. let xy = x : y
  301. let i = read xy
  302. if i < 0 || i >= 24
  303. then fail $ show $ MsgInvalidHour $ pack xy
  304. else return i
  305. minsec :: Num a => (Text -> FormMessage) -> Parser a
  306. minsec msg = do
  307. x <- digit
  308. y <- digit <|> fail (show $ msg $ pack [x])
  309. let xy = [x, y]
  310. let i = read xy
  311. if i < 0 || i >= 60
  312. then fail $ show $ msg $ pack xy
  313. else return $ fromIntegral (i :: Int)
  314. -- | Creates an input with @type="email"@. Yesod will validate the email's correctness according to RFC5322 and canonicalize it by removing comments and whitespace (see "Text.Email.Validate").
  315. emailField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Text
  316. emailField = Field
  317. { fieldParse = parseHelper $
  318. \s ->
  319. case Email.canonicalizeEmail $ encodeUtf8 s of
  320. Just e -> Right $ decodeUtf8With lenientDecode e
  321. Nothing -> Left $ MsgInvalidEmail s
  322. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  323. $newline never
  324. <input id="#{theId}" name="#{name}" *{attrs} type="email" :isReq:required="" value="#{either id id val}">
  325. |]
  326. , fieldEnctype = UrlEncoded
  327. }
  328. -- | Creates an input with @type="email"@ with the <http://w3c.github.io/html/sec-forms.html#the-multiple-attribute multiple> attribute; browsers might implement this as taking a comma separated list of emails. Each email address is validated as described in 'emailField'.
  329. --
  330. -- Since 1.3.7
  331. multiEmailField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m [Text]
  332. multiEmailField = Field
  333. { fieldParse = parseHelper $
  334. \s ->
  335. let addrs = map validate $ splitOn "," s
  336. in case partitionEithers addrs of
  337. ([], good) -> Right good
  338. (bad, _) -> Left $ MsgInvalidEmail $ cat bad
  339. , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
  340. $newline never
  341. <input id="#{theId}" name="#{name}" *{attrs} type="email" multiple :isReq:required="" value="#{either id cat val}">
  342. |]
  343. , fieldEnctype = UrlEncoded
  344. }
  345. where
  346. -- report offending address along with error
  347. validate a = case Email.validate $ encodeUtf8 a of
  348. Left e -> Left $ T.concat [a, " (", pack e, ")"]
  349. Right r -> Right $ emailToText r
  350. cat = intercalate ", "
  351. emailToText = decodeUtf8With lenientDecode . Email.toByteString
  352. type AutoFocus = Bool
  353. -- | Creates an input with @type="search"@. For <http://caniuse.com/#search=autofocus browsers without autofocus support>, a JS fallback is used if @AutoFocus@ is true.
  354. searchField :: Monad m => RenderMessage (HandlerSite m) FormMessage => AutoFocus -> Field m Text
  355. searchField autoFocus = Field
  356. { fieldParse = parseHelper Right
  357. , fieldView = \theId name attrs val isReq -> do
  358. [whamlet|
  359. $newline never
  360. <input id="#{theId}" name="#{name}" *{attrs} type="search" :isReq:required="" :autoFocus:autofocus="" value="#{either id id val}">
  361. |]
  362. when autoFocus $ do
  363. -- we want this javascript to be placed immediately after the field
  364. [whamlet|
  365. $newline never
  366. <script>if (!('autofocus' in document.createElement('input'))) {document.getElementById('#{theId}').focus();}
  367. |]
  368. toWidget [cassius|
  369. ##{theId}
  370. -webkit-appearance: textfield
  371. |]
  372. , fieldEnctype = UrlEncoded
  373. }
  374. -- | Creates an input with @type="url"@, validating the URL according to RFC3986.
  375. urlField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Text
  376. urlField = Field
  377. { fieldParse = parseHelper $ \s ->
  378. case parseURI $ unpack s of
  379. Nothing -> Left $ MsgInvalidUrl s
  380. Just _ -> Right s
  381. , fieldView = \theId name attrs val isReq ->
  382. [whamlet|<input ##{theId} name=#{name} *{attrs} type=url :isReq:required value=#{either id id val}>|]
  383. , fieldEnctype = UrlEncoded
  384. }
  385. -- | Creates a @\<select>@ tag for selecting one option. Example usage:
  386. --
  387. -- > areq (selectFieldList [("Value 1" :: Text, "value1"),("Value 2", "value2")]) "Which value?" Nothing
  388. selectFieldList :: (Eq a, RenderMessage site FormMessage, RenderMessage site msg)
  389. => [(msg, a)]
  390. -> Field (HandlerT site IO) a
  391. selectFieldList = selectField . optionsPairs
  392. -- | Creates a @\<select>@ tag for selecting one option. Example usage:
  393. --
  394. -- > areq (selectField $ optionsPairs [(MsgValue1, "value1"),(MsgValue2, "value2")]) "Which value?" Nothing
  395. selectField :: (Eq a, RenderMessage site FormMessage)
  396. => HandlerT site IO (OptionList a)
  397. -> Field (HandlerT site IO) a
  398. selectField = selectFieldHelper
  399. (\theId name attrs inside -> [whamlet|
  400. $newline never
  401. <select ##{theId} name=#{name} *{attrs}>^{inside}
  402. |]) -- outside
  403. (\_theId _name isSel -> [whamlet|
  404. $newline never
  405. <option value=none :isSel:selected>_{MsgSelectNone}
  406. |]) -- onOpt
  407. (\_theId _name _attrs value isSel text -> [whamlet|
  408. $newline never
  409. <option value=#{value} :isSel:selected>#{text}
  410. |]) -- inside
  411. -- | Creates a @\<select>@ tag for selecting multiple options.
  412. multiSelectFieldList :: (Eq a, RenderMessage site FormMessage, RenderMessage site msg)
  413. => [(msg, a)]
  414. -> Field (HandlerT site IO) [a]
  415. multiSelectFieldList = multiSelectField . optionsPairs
  416. -- | Creates a @\<select>@ tag for selecting multiple options.
  417. multiSelectField :: (Eq a, RenderMessage site FormMessage)
  418. => HandlerT site IO (OptionList a)
  419. -> Field (HandlerT site IO) [a]
  420. multiSelectField ioptlist =
  421. Field parse view UrlEncoded
  422. where
  423. parse [] _ = return $ Right Nothing
  424. parse optlist _ = do
  425. mapopt <- olReadExternal <$> ioptlist
  426. case mapM mapopt optlist of
  427. Nothing -> return $ Left "Error parsing values"
  428. Just res -> return $ Right $ Just res
  429. view theId name attrs val isReq = do
  430. opts <- fmap olOptions $ handlerToWidget ioptlist
  431. let selOpts = map (id &&& (optselected val)) opts
  432. [whamlet|
  433. <select ##{theId} name=#{name} :isReq:required multiple *{attrs}>
  434. $forall (opt, optsel) <- selOpts
  435. <option value=#{optionExternalValue opt} :optsel:selected>#{optionDisplay opt}
  436. |]
  437. where
  438. optselected (Left _) _ = False
  439. optselected (Right vals) opt = (optionInternalValue opt) `elem` vals
  440. -- | Creates an input with @type="radio"@ for selecting one option.
  441. radioFieldList :: (Eq a, RenderMessage site FormMessage, RenderMessage site msg)
  442. => [(msg, a)]
  443. -> Field (HandlerT site IO) a
  444. radioFieldList = radioField . optionsPairs
  445. -- | Creates an input with @type="checkbox"@ for selecting multiple options.
  446. checkboxesFieldList :: (Eq a, RenderMessage site FormMessage, RenderMessage site msg) => [(msg, a)]
  447. -> Field (HandlerT site IO) [a]
  448. checkboxesFieldList = checkboxesField . optionsPairs
  449. -- | Creates an input with @type="checkbox"@ for selecting multiple options.
  450. checkboxesField :: (Eq a, RenderMessage site FormMessage)
  451. => HandlerT site IO (OptionList a)
  452. -> Field (HandlerT site IO) [a]
  453. checkboxesField ioptlist = (multiSelectField ioptlist)
  454. { fieldView =
  455. \theId name attrs val isReq -> do
  456. opts <- fmap olOptions $ handlerToWidget ioptlist
  457. let optselected (Left _) _ = False
  458. optselected (Right vals) opt = (optionInternalValue opt) `elem` vals
  459. [whamlet|
  460. <span ##{theId}>
  461. $forall opt <- opts
  462. <label>
  463. <input type=checkbox name=#{name} value=#{optionExternalValue opt} *{attrs} :optselected val opt:checked>
  464. #{optionDisplay opt}
  465. |]
  466. }
  467. -- | Creates an input with @type="radio"@ for selecting one option.
  468. radioField :: (Eq a, RenderMessage site FormMessage)
  469. => HandlerT site IO (OptionList a)
  470. -> Field (HandlerT site IO) a
  471. radioField = selectFieldHelper
  472. (\theId _name _attrs inside -> [whamlet|
  473. $newline never
  474. <div ##{theId}>^{inside}
  475. |])
  476. (\theId name isSel -> [whamlet|
  477. $newline never
  478. <label .radio for=#{theId}-none>
  479. <div>
  480. <input id=#{theId}-none type=radio name=#{name} value=none :isSel:checked>
  481. _{MsgSelectNone}
  482. |])
  483. (\theId name attrs value isSel text -> [whamlet|
  484. $newline never
  485. <label .radio for=#{theId}-#{value}>
  486. <div>
  487. <input id=#{theId}-#{value} type=radio name=#{name} value=#{value} :isSel:checked *{attrs}>
  488. \#{text}
  489. |])
  490. -- | Creates a group of radio buttons to answer the question given in the message. Radio buttons are used to allow differentiating between an empty response (@Nothing@) and a no response (@Just False@). Consider using the simpler 'checkBoxField' if you don't need to make this distinction.
  491. --
  492. -- If this field is optional, the first radio button is labeled "\<None>", the second \"Yes" and the third \"No".
  493. --
  494. -- If this field is required, the first radio button is labeled \"Yes" and the second \"No".
  495. --
  496. -- (Exact label titles will depend on localization).
  497. boolField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Bool
  498. boolField = Field
  499. { fieldParse = \e _ -> return $ boolParser e
  500. , fieldView = \theId name attrs val isReq -> [whamlet|
  501. $newline never
  502. $if not isReq
  503. <input id=#{theId}-none *{attrs} type=radio name=#{name} value=none checked>
  504. <label for=#{theId}-none>_{MsgSelectNone}
  505. <input id=#{theId}-yes *{attrs} type=radio name=#{name} value=yes :showVal id val:checked>
  506. <label for=#{theId}-yes>_{MsgBoolYes}
  507. <input id=#{theId}-no *{attrs} type=radio name=#{name} value=no :showVal not val:checked>
  508. <label for=#{theId}-no>_{MsgBoolNo}
  509. |]
  510. , fieldEnctype = UrlEncoded
  511. }
  512. where
  513. boolParser [] = Right Nothing
  514. boolParser (x:_) = case x of
  515. "" -> Right Nothing
  516. "none" -> Right Nothing
  517. "yes" -> Right $ Just True
  518. "on" -> Right $ Just True
  519. "no" -> Right $ Just False
  520. "true" -> Right $ Just True
  521. "false" -> Right $ Just False
  522. t -> Left $ SomeMessage $ MsgInvalidBool t
  523. showVal = either (\_ -> False)
  524. -- | Creates an input with @type="checkbox"@.
  525. -- While the default @'boolField'@ implements a radio button so you
  526. -- can differentiate between an empty response (@Nothing@) and a no
  527. -- response (@Just False@), this simpler checkbox field returns an empty
  528. -- response as @Just False@.
  529. --
  530. -- Note that this makes the field always optional.
  531. --
  532. checkBoxField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m Bool
  533. checkBoxField = Field
  534. { fieldParse = \e _ -> return $ checkBoxParser e
  535. , fieldView = \theId name attrs val _ -> [whamlet|
  536. $newline never
  537. <input id=#{theId} *{attrs} type=checkbox name=#{name} value=yes :showVal id val:checked>
  538. |]
  539. , fieldEnctype = UrlEncoded
  540. }
  541. where
  542. checkBoxParser [] = Right $ Just False
  543. checkBoxParser (x:_) = case x of
  544. "yes" -> Right $ Just True
  545. "on" -> Right $ Just True
  546. _ -> Right $ Just False
  547. showVal = either (\_ -> False)
  548. -- | A structure holding a list of options. Typically you can use a convenience function like 'mkOptionList' or 'optionsPairs' instead of creating this directly.
  549. data OptionList a = OptionList
  550. { olOptions :: [Option a]
  551. , olReadExternal :: Text -> Maybe a -- ^ A function mapping from the form's value ('optionExternalValue') to the selected Haskell value ('optionInternalValue').
  552. }
  553. -- | Since 1.4.6
  554. instance Functor OptionList where
  555. fmap f (OptionList options readExternal) =
  556. OptionList ((fmap.fmap) f options) (fmap f . readExternal)
  557. -- | Creates an 'OptionList', using a 'Map' to implement the 'olReadExternal' function.
  558. mkOptionList :: [Option a] -> OptionList a
  559. mkOptionList os = OptionList
  560. { olOptions = os
  561. , olReadExternal = flip Map.lookup $ Map.fromList $ map (optionExternalValue &&& optionInternalValue) os
  562. }
  563. data Option a = Option
  564. { optionDisplay :: Text -- ^ The user-facing label.
  565. , optionInternalValue :: a -- ^ The Haskell value being selected.
  566. , optionExternalValue :: Text -- ^ The representation of this value stored in the form.
  567. }
  568. -- | Since 1.4.6
  569. instance Functor Option where
  570. fmap f (Option display internal external) = Option display (f internal) external
  571. -- | Creates an 'OptionList' from a list of (display-value, internal value) pairs.
  572. optionsPairs :: (MonadHandler m, RenderMessage (HandlerSite m) msg)
  573. => [(msg, a)] -> m (OptionList a)
  574. optionsPairs opts = do
  575. mr <- getMessageRender
  576. let mkOption external (display, internal) =
  577. Option { optionDisplay = mr display
  578. , optionInternalValue = internal
  579. , optionExternalValue = pack $ show external
  580. }
  581. return $ mkOptionList (zipWith mkOption [1 :: Int ..] opts)
  582. -- | Creates an 'OptionList' from an 'Enum', using its 'Show' instance for the user-facing value.
  583. optionsEnum :: (MonadHandler m, Show a, Enum a, Bounded a) => m (OptionList a)
  584. optionsEnum = optionsPairs $ map (\x -> (pack $ show x, x)) [minBound..maxBound]
  585. -- | Selects a list of 'Entity's with the given 'Filter' and 'SelectOpt's. The @(a -> msg)@ function is then used to derive the display value for an 'OptionList'. Example usage:
  586. --
  587. -- > Country
  588. -- > name Text
  589. -- > deriving Eq -- Must derive Eq
  590. --
  591. -- > data CountryForm = CountryForm
  592. -- > { country :: Entity Country
  593. -- > }
  594. -- >
  595. -- > countryNameForm :: AForm Handler CountryForm
  596. -- > countryNameForm = CountryForm
  597. -- > <$> areq (selectField countries) "Which country do you live in?" Nothing
  598. -- > where
  599. -- > countries = optionsPersist [] [Asc CountryName] countryName
  600. #if MIN_VERSION_persistent(2,5,0)
  601. optionsPersist :: ( YesodPersist site
  602. , PersistQueryRead backend
  603. , PathPiece (Key a)
  604. , RenderMessage site msg
  605. , YesodPersistBackend site ~ backend
  606. , PersistRecordBackend a backend
  607. )
  608. => [Filter a]
  609. -> [SelectOpt a]
  610. -> (a -> msg)
  611. -> HandlerT site IO (OptionList (Entity a))
  612. #else
  613. optionsPersist :: ( YesodPersist site, PersistEntity a
  614. , PersistQuery (PersistEntityBackend a)
  615. , PathPiece (Key a)
  616. , RenderMessage site msg
  617. , YesodPersistBackend site ~ PersistEntityBackend a
  618. )
  619. => [Filter a]
  620. -> [SelectOpt a]
  621. -> (a -> msg)
  622. -> HandlerT site IO (OptionList (Entity a))
  623. #endif
  624. optionsPersist filts ords toDisplay = fmap mkOptionList $ do
  625. mr <- getMessageRender
  626. pairs <- runDB $ selectList filts ords
  627. return $ map (\(Entity key value) -> Option
  628. { optionDisplay = mr (toDisplay value)
  629. , optionInternalValue = Entity key value
  630. , optionExternalValue = toPathPiece key
  631. }) pairs
  632. -- | An alternative to 'optionsPersist' which returns just the 'Key' instead of
  633. -- the entire 'Entity'.
  634. --
  635. -- Since 1.3.2
  636. #if MIN_VERSION_persistent(2,5,0)
  637. optionsPersistKey
  638. :: (YesodPersist site
  639. , PersistQueryRead backend
  640. , PathPiece (Key a)
  641. , RenderMessage site msg
  642. , backend ~ YesodPersistBackend site
  643. , PersistRecordBackend a backend
  644. )
  645. => [Filter a]
  646. -> [SelectOpt a]
  647. -> (a -> msg)
  648. -> HandlerT site IO (OptionList (Key a))
  649. #else
  650. optionsPersistKey
  651. :: (YesodPersist site
  652. , PersistEntity a
  653. , PersistQuery (PersistEntityBackend a)
  654. , PathPiece (Key a)
  655. , RenderMessage site msg
  656. , YesodPersistBackend site ~ PersistEntityBackend a
  657. )
  658. => [Filter a]
  659. -> [SelectOpt a]
  660. -> (a -> msg)
  661. -> HandlerT site IO (OptionList (Key a))
  662. #endif
  663. optionsPersistKey filts ords toDisplay = fmap mkOptionList $ do
  664. mr <- getMessageRender
  665. pairs <- runDB $ selectList filts ords
  666. return $ map (\(Entity key value) -> Option
  667. { optionDisplay = mr (toDisplay value)
  668. , optionInternalValue = key
  669. , optionExternalValue = toPathPiece key
  670. }) pairs
  671. selectFieldHelper
  672. :: (Eq a, RenderMessage site FormMessage)
  673. => (Text -> Text -> [(Text, Text)] -> WidgetT site IO () -> WidgetT site IO ())
  674. -> (Text -> Text -> Bool -> WidgetT site IO ())
  675. -> (Text -> Text -> [(Text, Text)] -> Text -> Bool -> Text -> WidgetT site IO ())
  676. -> HandlerT site IO (OptionList a)
  677. -> Field (HandlerT site IO) a
  678. selectFieldHelper outside onOpt inside opts' = Field
  679. { fieldParse = \x _ -> do
  680. opts <- opts'
  681. return $ selectParser opts x
  682. , fieldView = \theId name attrs val isReq -> do
  683. opts <- fmap olOptions $ handlerToWidget opts'
  684. outside theId name attrs $ do
  685. unless isReq $ onOpt theId name $ not $ render opts val `elem` map optionExternalValue opts
  686. flip mapM_ opts $ \opt -> inside
  687. theId
  688. name
  689. ((if isReq then (("required", "required"):) else id) attrs)
  690. (optionExternalValue opt)
  691. ((render opts val) == optionExternalValue opt)
  692. (optionDisplay opt)
  693. , fieldEnctype = UrlEncoded
  694. }
  695. where
  696. render _ (Left _) = ""
  697. render opts (Right a) = maybe "" optionExternalValue $ listToMaybe $ filter ((== a) . optionInternalValue) opts
  698. selectParser _ [] = Right Nothing
  699. selectParser opts (s:_) = case s of
  700. "" -> Right Nothing
  701. "none" -> Right Nothing
  702. x -> case olReadExternal opts x of
  703. Nothing -> Left $ SomeMessage $ MsgInvalidEntry x
  704. Just y -> Right $ Just y
  705. -- | Creates an input with @type="file"@.
  706. fileField :: (Monad m, RenderMessage (HandlerSite m) FormMessage)
  707. => Field m FileInfo
  708. fileField = Field
  709. { fieldParse = \_ files -> return $
  710. case files of
  711. [] -> Right Nothing
  712. file:_ -> Right $ Just file
  713. , fieldView = \id' name attrs _ isReq -> toWidget [hamlet|
  714. <input id=#{id'} name=#{name} *{attrs} type=file :isReq:required>
  715. |]
  716. , fieldEnctype = Multipart
  717. }
  718. fileAFormReq :: (MonadHandler m, RenderMessage (HandlerSite m) FormMessage)
  719. => FieldSettings (HandlerSite m) -> AForm m FileInfo
  720. fileAFormReq fs = AForm $ \(site, langs) menvs ints -> do
  721. let (name, ints') =
  722. case fsName fs of
  723. Just x -> (x, ints)
  724. Nothing ->
  725. let i' = incrInts ints
  726. in (pack $ 'f' : show i', i')
  727. id' <- maybe newIdent return $ fsId fs
  728. let (res, errs) =
  729. case menvs of
  730. Nothing -> (FormMissing, Nothing)
  731. Just (_, fenv) ->
  732. case Map.lookup name fenv of
  733. Just (fi:_) -> (FormSuccess fi, Nothing)
  734. _ ->
  735. let t = renderMessage site langs MsgValueRequired
  736. in (FormFailure [t], Just $ toHtml t)
  737. let fv = FieldView
  738. { fvLabel = toHtml $ renderMessage site langs $ fsLabel fs
  739. , fvTooltip = fmap (toHtml . renderMessage site langs) $ fsTooltip fs
  740. , fvId = id'
  741. , fvInput = [whamlet|
  742. $newline never
  743. <input type=file name=#{name} ##{id'} *{fsAttrs fs}>
  744. |]
  745. , fvErrors = errs
  746. , fvRequired = True
  747. }
  748. return (res, (fv :), ints', Multipart)
  749. fileAFormOpt :: MonadHandler m
  750. => RenderMessage (HandlerSite m) FormMessage
  751. => FieldSettings (HandlerSite m)
  752. -> AForm m (Maybe FileInfo)
  753. fileAFormOpt fs = AForm $ \(master, langs) menvs ints -> do
  754. let (name, ints') =
  755. case fsName fs of
  756. Just x -> (x, ints)
  757. Nothing ->
  758. let i' = incrInts ints
  759. in (pack $ 'f' : show i', i')
  760. id' <- maybe newIdent return $ fsId fs
  761. let (res, errs) =
  762. case menvs of
  763. Nothing -> (FormMissing, Nothing)
  764. Just (_, fenv) ->
  765. case Map.lookup name fenv of
  766. Just (fi:_) -> (FormSuccess $ Just fi, Nothing)
  767. _ -> (FormSuccess Nothing, Nothing)
  768. let fv = FieldView
  769. { fvLabel = toHtml $ renderMessage master langs $ fsLabel fs
  770. , fvTooltip = fmap (toHtml . renderMessage master langs) $ fsTooltip fs
  771. , fvId = id'
  772. , fvInput = [whamlet|
  773. $newline never
  774. <input type=file name=#{name} ##{id'} *{fsAttrs fs}>
  775. |]
  776. , fvErrors = errs
  777. , fvRequired = False
  778. }
  779. return (res, (fv :), ints', Multipart)
  780. incrInts :: Ints -> Ints
  781. incrInts (IntSingle i) = IntSingle $ i + 1
  782. incrInts (IntCons i is) = (i + 1) `IntCons` is
  783. -- | Adds a '0' to some text so that it may be recognized as a double.
  784. -- The read ftn does not recognize ".3" as 0.3 nor "-.3" as -0.3, so this
  785. -- function changes ".xxx" to "0.xxx" and "-.xxx" to "-0.xxx"
  786. prependZero :: Text -> Text
  787. prependZero t0 = if T.null t1
  788. then t1
  789. else if T.head t1 == '.'
  790. then '0' `T.cons` t1
  791. else if "-." `T.isPrefixOf` t1
  792. then "-0." `T.append` (T.drop 2 t1)
  793. else t1
  794. where t1 = T.dropWhile ((==) ' ') t0
  795. -- $optionsOverview
  796. -- These functions create inputs where one or more options can be selected from a list.
  797. --
  798. -- The basic datastructure used is an 'Option', which combines a user-facing display value, the internal Haskell value being selected, and an external 'Text' stored as the @value@ in the form (used to map back to the internal value). A list of these, together with a function mapping from an external value back to a Haskell value, form an 'OptionList', which several of these functions take as an argument.
  799. --
  800. -- Typically, you won't need to create an 'OptionList' directly and can instead make one with functions like 'optionsPairs' or 'optionsEnum'. Alternatively, you can use functions like 'selectFieldList', which use their @[(msg, a)]@ parameter to create an 'OptionList' themselves.