{- git-annex assistant webapp form utilities - - Copyright 2012 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} {-# LANGUAGE FlexibleContexts, TypeFamilies, QuasiQuotes #-} {-# LANGUAGE MultiParamTypeClasses, TemplateHaskell #-} {-# LANGUAGE OverloadedStrings, RankNTypes #-} {-# LANGUAGE CPP #-} module Assistant.WebApp.Form where import Assistant.WebApp.Types import Assistant.Gpg #if MIN_VERSION_yesod(1,2,0) import Yesod hiding (textField, passwordField) import Yesod.Form.Fields as F #else import Yesod hiding (textField, passwordField, selectField, selectFieldList) import Yesod.Form.Fields as F hiding (selectField, selectFieldList) import Data.String (IsString (..)) import Control.Monad (unless) import Data.Maybe (listToMaybe) #endif #if MIN_VERSION_yesod_form(1,3,8) import Yesod.Form.Bootstrap3 as Y hiding (bfs) #else import Assistant.WebApp.Bootstrap3 as Y hiding (bfs) #endif import Data.Text (Text) {- Yesod's textField sets the required attribute for required fields. - We don't want this, because many of the forms used in this webapp - display a modal dialog when submitted, which interacts badly with - required field handling by the browser. - - Required fields are still checked by Yesod. -} textField :: MkField Text textField = F.textField { fieldView = \theId name attrs val _isReq -> [whamlet| |] } readonlyTextField :: MkField Text readonlyTextField = F.textField { fieldView = \theId name attrs val _isReq -> [whamlet| |] } {- Also without required attribute. -} passwordField :: MkField Text passwordField = F.passwordField { fieldView = \theId name attrs val _isReq -> toWidget [hamlet| |] } {- In older Yesod versions attrs is written into the