Merge pull request #1722 from schoettl/selectFieldGrouped

Forms: selectFieldGrouped
This commit is contained in:
Michael Snoyman 2021-04-15 08:58:21 +03:00 committed by GitHub
commit cf3d9db87d
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
9 changed files with 110 additions and 30 deletions

View File

@ -21,7 +21,7 @@ data Wiki = Wiki
} }
-- | A typeclass that all master sites that want a Wiki must implement. A -- | A typeclass that all master sites that want a Wiki must implement. A
-- master must be able to render form messages, as we use yesod-forms for -- master must be able to render form messages, as we use yesod-form for
-- processing user input. -- processing user input.
class (RenderMessage master FormMessage, Yesod master) => YesodWiki master where class (RenderMessage master FormMessage, Yesod master) => YesodWiki master where
-- | Write protection. By default, no protection. -- | Write protection. By default, no protection.

View File

@ -22,7 +22,7 @@ library
, unliftio , unliftio
, yesod-auth >= 1.6 && < 1.7 , yesod-auth >= 1.6 && < 1.7
, yesod-core >= 1.6 && < 1.7 , yesod-core >= 1.6 && < 1.7
, yesod-form >= 1.6 && < 1.7 , yesod-form >= 1.6 && < 1.8
exposed-modules: Yesod.Auth.OAuth exposed-modules: Yesod.Auth.OAuth
ghc-options: -Wall ghc-options: -Wall

View File

@ -57,7 +57,7 @@ library
, unordered-containers , unordered-containers
, wai >= 1.4 , wai >= 1.4
, yesod-core >= 1.6 && < 1.7 , yesod-core >= 1.6 && < 1.7
, yesod-form >= 1.6 && < 1.7 , yesod-form >= 1.6 && < 1.8
, yesod-persistent >= 1.6 , yesod-persistent >= 1.6
if flag(network-uri) if flag(network-uri)

View File

@ -26,7 +26,7 @@ library
, text >= 0.9 , text >= 0.9
, transformers >= 0.2.2 , transformers >= 0.2.2
, yesod-core >= 1.6 && < 1.7 , yesod-core >= 1.6 && < 1.7
, yesod-form >= 1.6 && < 1.7 , yesod-form >= 1.6 && < 1.8
if flag(network-uri) if flag(network-uri)
build-depends: network-uri >= 2.6 build-depends: network-uri >= 2.6

View File

@ -1,5 +1,9 @@
# ChangeLog for yesod-form # ChangeLog for yesod-form
## 1.7.0
* Extended `OptionList` by `OptionListGrouped` and implemented grouped select fields (`<select>` with `<optgroup>`) [#1722](https://github.com/yesodweb/yesod/pull/1722)
## 1.6.7 ## 1.6.7
* Added equivalent version of `mreqMsg` for `areq` and `wreq` correspondingly [#1628](https://github.com/yesodweb/yesod/pull/1628) * Added equivalent version of `mreqMsg` for `areq` and `wreq` correspondingly [#1628](https://github.com/yesodweb/yesod/pull/1628)

View File

@ -3,7 +3,7 @@
Form handling for Yesod, in the same style as formlets. See [the forms Form handling for Yesod, in the same style as formlets. See [the forms
chapter](http://www.yesodweb.com/book/forms) of the Yesod book. chapter](http://www.yesodweb.com/book/forms) of the Yesod book.
This package provies a set of basic form inputs such as text, number, time, This package provides a set of basic form inputs such as text, number, time,
checkbox, select, textarea, and etc. via `Yesod.Form.Fields` module. Also, checkbox, select, textarea, and etc. via `Yesod.Form.Fields` module. Also,
there is `Yesod.Form.Nic` module providing richtext field using Nic editor. there is `Yesod.Form.Nic` module providing richtext field using Nic editor.
However, this module is grandfathered now and Nic editor is not actively However, this module is grandfathered now and Nic editor is not actively

View File

@ -3,6 +3,7 @@
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
-- | Field functions allow you to easily create and validate forms, cleanly handling the uncertainty of parsing user input. -- | Field functions allow you to easily create and validate forms, cleanly handling the uncertainty of parsing user input.
@ -45,6 +46,7 @@ module Yesod.Form.Fields
, selectFieldHelper , selectFieldHelper
, selectField , selectField
, selectFieldList , selectFieldList
, selectFieldListGrouped
, radioField , radioField
, radioFieldList , radioFieldList
, checkboxesField , checkboxesField
@ -54,9 +56,11 @@ module Yesod.Form.Fields
, Option (..) , Option (..)
, OptionList (..) , OptionList (..)
, mkOptionList , mkOptionList
, mkOptionListGrouped
, optionsPersist , optionsPersist
, optionsPersistKey , optionsPersistKey
, optionsPairs , optionsPairs
, optionsPairsGrouped
, optionsEnum , optionsEnum
) where ) where
@ -80,7 +84,7 @@ import Database.Persist (Entity (..), SqlType (SqlString), PersistRecordBackend,
import Database.Persist (Entity (..), SqlType (SqlString), PersistEntity, PersistQuery, PersistEntityBackend) import Database.Persist (Entity (..), SqlType (SqlString), PersistEntity, PersistQuery, PersistEntityBackend)
#endif #endif
import Text.HTML.SanitizeXSS (sanitizeBalance) import Text.HTML.SanitizeXSS (sanitizeBalance)
import Control.Monad (when, unless) import Control.Monad (when, unless, forM_)
import Data.Either (partitionEithers) import Data.Either (partitionEithers)
import Data.Maybe (listToMaybe, fromMaybe) import Data.Maybe (listToMaybe, fromMaybe)
@ -172,7 +176,7 @@ timeField = timeFieldTypeTime
-- --
-- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function. -- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function.
-- --
-- Since 1.4.2 -- @since 1.4.2
timeFieldTypeTime :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay timeFieldTypeTime :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay
timeFieldTypeTime = timeFieldOfType "time" timeFieldTypeTime = timeFieldOfType "time"
@ -182,7 +186,7 @@ timeFieldTypeTime = timeFieldOfType "time"
-- --
-- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function. -- Add the @time@ package and import the "Data.Time.LocalTime" module to use this function.
-- --
-- Since 1.4.2 -- @since 1.4.2
timeFieldTypeText :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay timeFieldTypeText :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m TimeOfDay
timeFieldTypeText = timeFieldOfType "text" timeFieldTypeText = timeFieldOfType "text"
@ -362,7 +366,7 @@ $newline never
-- | 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'. -- | 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'.
-- --
-- Since 1.3.7 -- @since 1.3.7
multiEmailField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m [Text] multiEmailField :: Monad m => RenderMessage (HandlerSite m) FormMessage => Field m [Text]
multiEmailField = Field multiEmailField = Field
{ fieldParse = parseHelper $ { fieldParse = parseHelper $
@ -427,7 +431,15 @@ selectFieldList :: (Eq a, RenderMessage site FormMessage, RenderMessage site msg
-> Field (HandlerFor site) a -> Field (HandlerFor site) a
selectFieldList = selectField . optionsPairs selectFieldList = selectField . optionsPairs
-- | Creates a @\<select>@ tag for selecting one option. Example usage: -- | Creates a @\<select>@ tag with @\<optgroup>@s for selecting one option.
--
-- @since 1.7.0
selectFieldListGrouped :: (Eq a, RenderMessage site FormMessage, RenderMessage site msg)
=> [(msg, [(msg, a)])]
-> Field (HandlerFor site) a
selectFieldListGrouped = selectField . optionsPairsGrouped
-- | Creates a @\<select>@ tag with optional @\<optgroup>@s for selecting one option. Example usage:
-- --
-- > areq (selectField $ optionsPairs [(MsgValue1, "value1"),(MsgValue2, "value2")]) "Which value?" Nothing -- > areq (selectField $ optionsPairs [(MsgValue1, "value1"),(MsgValue2, "value2")]) "Which value?" Nothing
selectField :: (Eq a, RenderMessage site FormMessage) selectField :: (Eq a, RenderMessage site FormMessage)
@ -446,6 +458,9 @@ $newline never
$newline never $newline never
<option value=#{value} :isSel:selected>#{text} <option value=#{value} :isSel:selected>#{text}
|]) -- inside |]) -- inside
(Just $ \label -> [whamlet|
<optgroup label=#{label}>
|]) -- group label
-- | Creates a @\<select>@ tag for selecting multiple options. -- | Creates a @\<select>@ tag for selecting multiple options.
multiSelectFieldList :: (Eq a, RenderMessage site msg) multiSelectFieldList :: (Eq a, RenderMessage site msg)
@ -531,6 +546,7 @@ $newline never
<input id=#{theId}-#{value} type=radio name=#{name} value=#{value} :isSel:checked *{attrs}> <input id=#{theId}-#{value} type=radio name=#{name} value=#{value} :isSel:checked *{attrs}>
\#{text} \#{text}
|]) |])
Nothing
-- | 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. -- | 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.
-- --
@ -598,15 +614,31 @@ $newline never
showVal = either (\_ -> False) showVal = either (\_ -> False)
-- | A structure holding a list of options. Typically you can use a convenience function like 'mkOptionList' or 'optionsPairs' instead of creating this directly. -- | A structure holding a list of options. Typically you can use a convenience function like 'mkOptionList' or 'optionsPairs' instead of creating this directly.
data OptionList a = OptionList --
-- Extended by 'OptionListGrouped' in 1.7.0.
data OptionList a
= OptionList
{ olOptions :: [Option a] { olOptions :: [Option a]
, olReadExternal :: Text -> Maybe a -- ^ A function mapping from the form's value ('optionExternalValue') to the selected Haskell value ('optionInternalValue'). , olReadExternal :: Text -> Maybe a -- ^ A function mapping from the form's value ('optionExternalValue') to the selected Haskell value ('optionInternalValue').
} }
| OptionListGrouped
{ olOptionsGrouped :: [(Text, [Option a])]
, olReadExternalGrouped :: Text -> Maybe a -- ^ A function mapping from the form's value ('optionExternalValue') to the selected Haskell value ('optionInternalValue').
}
-- | Since 1.4.6 -- | Convert grouped 'OptionList' to a normal one.
--
-- @since 1.7.0
flattenOptionList :: OptionList a -> OptionList a
flattenOptionList (OptionListGrouped os re) = OptionList (concatMap snd os) re
flattenOptionList ol = ol
-- | @since 1.4.6
instance Functor OptionList where instance Functor OptionList where
fmap f (OptionList options readExternal) = fmap f (OptionList options readExternal) =
OptionList ((fmap.fmap) f options) (fmap f . readExternal) OptionList ((fmap.fmap) f options) (fmap f . readExternal)
fmap f (OptionListGrouped options readExternal) =
OptionListGrouped (map (\(g, os) -> (g, (fmap.fmap) f os)) options) (fmap f . readExternal)
-- | Creates an 'OptionList', using a 'Map' to implement the 'olReadExternal' function. -- | Creates an 'OptionList', using a 'Map' to implement the 'olReadExternal' function.
mkOptionList :: [Option a] -> OptionList a mkOptionList :: [Option a] -> OptionList a
@ -615,13 +647,22 @@ mkOptionList os = OptionList
, olReadExternal = flip Map.lookup $ Map.fromList $ map (optionExternalValue &&& optionInternalValue) os , olReadExternal = flip Map.lookup $ Map.fromList $ map (optionExternalValue &&& optionInternalValue) os
} }
-- | Creates an 'OptionList', using a 'Map' to implement the 'olReadExternalGrouped' function.
--
-- @since 1.7.0
mkOptionListGrouped :: [(Text, [Option a])] -> OptionList a
mkOptionListGrouped os = OptionListGrouped
{ olOptionsGrouped = os
, olReadExternalGrouped = flip Map.lookup $ Map.fromList $ map (optionExternalValue &&& optionInternalValue) $ concatMap snd os
}
data Option a = Option data Option a = Option
{ optionDisplay :: Text -- ^ The user-facing label. { optionDisplay :: Text -- ^ The user-facing label.
, optionInternalValue :: a -- ^ The Haskell value being selected. , optionInternalValue :: a -- ^ The Haskell value being selected.
, optionExternalValue :: Text -- ^ The representation of this value stored in the form. , optionExternalValue :: Text -- ^ The representation of this value stored in the form.
} }
-- | Since 1.4.6 -- | @since 1.4.6
instance Functor Option where instance Functor Option where
fmap f (Option display internal external) = Option display (f internal) external fmap f (Option display internal external) = Option display (f internal) external
@ -637,6 +678,30 @@ optionsPairs opts = do
} }
return $ mkOptionList (zipWith mkOption [1 :: Int ..] opts) return $ mkOptionList (zipWith mkOption [1 :: Int ..] opts)
-- | Creates an 'OptionList' from a list of (display-value, internal value) pairs.
--
-- @since 1.7.0
optionsPairsGrouped
:: forall m msg a. (MonadHandler m, RenderMessage (HandlerSite m) msg)
=> [(msg, [(msg, a)])] -> m (OptionList a)
optionsPairsGrouped opts = do
mr <- getMessageRender
let mkOption (external, (display, internal)) =
Option { optionDisplay = mr display
, optionInternalValue = internal
, optionExternalValue = pack $ show external
}
opts' = enumerateSublists opts :: [(msg, [(Int, (msg, a))])]
opts'' = map (\(x, ys) -> (mr x, map mkOption ys)) opts'
return $ mkOptionListGrouped opts''
-- | Helper to enumerate sublists with one consecutive index.
enumerateSublists :: forall a b. [(a, [b])] -> [(a, [(Int, b)])]
enumerateSublists xss =
let yss :: [(Int, (a, [b]))]
yss = snd $ foldl (\(i, res) xs -> (i + (length.snd) xs, res ++ [(i, xs)])) (1, []) xss
in map (\(i, (x, ys)) -> (x, zip [i :: Int ..] ys)) yss
-- | Creates an 'OptionList' from an 'Enum', using its 'Show' instance for the user-facing value. -- | Creates an 'OptionList' from an 'Enum', using its 'Show' instance for the user-facing value.
optionsEnum :: (MonadHandler m, Show a, Enum a, Bounded a) => m (OptionList a) optionsEnum :: (MonadHandler m, Show a, Enum a, Bounded a) => m (OptionList a)
optionsEnum = optionsPairs $ map (\x -> (pack $ show x, x)) [minBound..maxBound] optionsEnum = optionsPairs $ map (\x -> (pack $ show x, x)) [minBound..maxBound]
@ -692,7 +757,7 @@ optionsPersist filts ords toDisplay = fmap mkOptionList $ do
-- | An alternative to 'optionsPersist' which returns just the 'Key' instead of -- | An alternative to 'optionsPersist' which returns just the 'Key' instead of
-- the entire 'Entity'. -- the entire 'Entity'.
-- --
-- Since 1.3.2 -- @since 1.3.2
#if MIN_VERSION_persistent(2,5,0) #if MIN_VERSION_persistent(2,5,0)
optionsPersistKey optionsPersistKey
:: (YesodPersist site :: (YesodPersist site
@ -731,7 +796,7 @@ optionsPersistKey filts ords toDisplay = fmap mkOptionList $ do
}) pairs }) pairs
-- | -- |
-- A helper function for constucting 'selectField's. You may want to use this when you define your custom 'selectField's or 'radioField's. -- A helper function for constucting 'selectField's with optional option groups. You may want to use this when you define your custom 'selectField's or 'radioField's.
-- --
-- @since 1.6.2 -- @since 1.6.2
selectFieldHelper selectFieldHelper
@ -739,23 +804,26 @@ selectFieldHelper
=> (Text -> Text -> [(Text, Text)] -> WidgetFor site () -> WidgetFor site ()) -- ^ Outermost part of the field => (Text -> Text -> [(Text, Text)] -> WidgetFor site () -> WidgetFor site ()) -- ^ Outermost part of the field
-> (Text -> Text -> Bool -> WidgetFor site ()) -- ^ An option for None if the field is optional -> (Text -> Text -> Bool -> WidgetFor site ()) -- ^ An option for None if the field is optional
-> (Text -> Text -> [(Text, Text)] -> Text -> Bool -> Text -> WidgetFor site ()) -- ^ Other options -> (Text -> Text -> [(Text, Text)] -> Text -> Bool -> Text -> WidgetFor site ()) -- ^ Other options
-> (Maybe (Text -> WidgetFor site ())) -- ^ Group headers placed inbetween options
-> HandlerFor site (OptionList a) -> HandlerFor site (OptionList a)
-> Field (HandlerFor site) a -> Field (HandlerFor site) a
selectFieldHelper outside onOpt inside opts' = Field selectFieldHelper outside onOpt inside grpHdr opts' = Field
{ fieldParse = \x _ -> do { fieldParse = \x _ -> do
opts <- opts' opts <- fmap flattenOptionList opts'
return $ selectParser opts x return $ selectParser opts x
, fieldView = \theId name attrs val isReq -> do , fieldView = \theId name attrs val isReq -> do
opts <- fmap olOptions $ handlerToWidget opts'
outside theId name attrs $ do outside theId name attrs $ do
unless isReq $ onOpt theId name $ not $ render opts val `elem` map optionExternalValue opts optsFlat <- fmap (olOptions.flattenOptionList) $ handlerToWidget opts'
flip mapM_ opts $ \opt -> inside unless isReq $ onOpt theId name $ render optsFlat val `notElem` map optionExternalValue optsFlat
theId opts'' <- handlerToWidget opts'
name case opts'' of
((if isReq then (("required", "required"):) else id) attrs) OptionList{} -> constructOptions theId name attrs val isReq optsFlat
(optionExternalValue opt) OptionListGrouped{olOptionsGrouped=grps} -> do
((render opts val) == optionExternalValue opt) forM_ grps $ \(grp, opts) -> do
(optionDisplay opt) case grpHdr of
Just hdr -> hdr grp
Nothing -> return ()
constructOptions theId name attrs val isReq opts
, fieldEnctype = UrlEncoded , fieldEnctype = UrlEncoded
} }
where where
@ -768,6 +836,14 @@ selectFieldHelper outside onOpt inside opts' = Field
x -> case olReadExternal opts x of x -> case olReadExternal opts x of
Nothing -> Left $ SomeMessage $ MsgInvalidEntry x Nothing -> Left $ SomeMessage $ MsgInvalidEntry x
Just y -> Right $ Just y Just y -> Right $ Just y
constructOptions theId name attrs val isReq opts =
forM_ opts $ \opt -> inside
theId
name
((if isReq then (("required", "required"):) else id) attrs)
(optionExternalValue opt)
(render opts val == optionExternalValue opt)
(optionDisplay opt)
-- | Creates an input with @type="file"@. -- | Creates an input with @type="file"@.
fileField :: Monad m fileField :: Monad m
@ -864,7 +940,7 @@ prependZero t0 = if T.null t1
then "-0." `T.append` (T.drop 2 t1) then "-0." `T.append` (T.drop 2 t1)
else t1 else t1
where t1 = T.dropWhile ((==) ' ') t0 where t1 = T.dropWhile (==' ') t0
-- $optionsOverview -- $optionsOverview
-- These functions create inputs where one or more options can be selected from a list. -- These functions create inputs where one or more options can be selected from a list.

View File

@ -1,5 +1,5 @@
name: yesod-form name: yesod-form
version: 1.6.7 version: 1.7.0
license: MIT license: MIT
license-file: LICENSE license-file: LICENSE
author: Michael Snoyman <michael@snoyman.com> author: Michael Snoyman <michael@snoyman.com>

View File

@ -38,7 +38,7 @@ library
, warp >= 1.3 , warp >= 1.3
, yaml >= 0.8.17 , yaml >= 0.8.17
, yesod-core >= 1.6 && < 1.7 , yesod-core >= 1.6 && < 1.7
, yesod-form >= 1.6 && < 1.7 , yesod-form >= 1.6 && < 1.8
, yesod-persistent >= 1.6 && < 1.7 , yesod-persistent >= 1.6 && < 1.7
exposed-modules: Yesod exposed-modules: Yesod