{-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} module Yesod.Form.Bulma.Fields ( bulmaIntField , bulmaTextField , bulmaEmailField , bulmaTextareaField , bulmaCheckBoxField , bulmaRadioFieldList , bulmaRadioField , bulmaSelectFieldList , bulmaSelectField , bulmaCheckboxesFieldList , bulmaCheckboxesField , bulmaMultiSelectFieldList , bulmaMultiSelectField ) where import Control.Arrow ((&&&)) import Control.Monad (forM_, unless) import Data.Maybe (listToMaybe) import Data.Text (Text, pack) import Data.Text.Encoding (decodeUtf8With, encodeUtf8) import Data.Text.Encoding.Error (lenientDecode) import Data.Text.Read (decimal, signed) import qualified Text.Email.Validate as Email import Text.Shakespeare.I18N (RenderMessage, SomeMessage (..)) import Yesod.Core (HandlerSite) import Yesod.Core.Types (HandlerFor, WidgetFor) import Yesod.Core.Widget (handlerToWidget, whamlet) import Yesod.Form.Bulma.Class import Yesod.Form.Bulma.Utils (addStylesheet') import Yesod.Form.Fields (FormMessage (..), Option (..), OptionList (..), Textarea (..), optionsPairs) import Yesod.Form.Functions (parseHelper) import Yesod.Form.Types (Enctype (..), Field (..)) -- | Creates an input with @type="checkbox"@ for selecting multiple options. bulmaCheckboxesFieldList :: ( YesodBulma site , Eq a , RenderMessage site msg ) => [(msg, a)] -> Field (HandlerFor site) [a] bulmaCheckboxesFieldList = bulmaCheckboxesField . optionsPairs -- | Creates an input with @type="checkbox"@ for selecting multiple options. bulmaCheckboxesField :: ( YesodBulma site , Eq a ) => HandlerFor site (OptionList a) -> Field (HandlerFor site) [a] bulmaCheckboxesField ioptlist = (bulmaMultiSelectField ioptlist) { fieldView = \theId name attrs val _isReq -> do opts <- olOptions <$> handlerToWidget ioptlist let optselected (Left _) _ = False optselected (Right vals) opt = optionInternalValue opt `elem` vals addStylesheet' urlBulmaExCheckRadio [whamlet| $newline never
$forall opt <- opts