{- 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 #-} module Assistant.WebApp.Form where import Types.Remote (RemoteConfigKey) import Yesod hiding (textField, passwordField) import Yesod.Form.Fields as F 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 :: RenderMessage master FormMessage => Field sub master Text textField = F.textField { fieldView = \theId name attrs val _isReq -> [whamlet| |] } {- Also without required attribute. -} passwordField :: RenderMessage master FormMessage => Field sub master Text passwordField = F.passwordField { fieldView = \theId name attrs val _isReq -> toWidget [hamlet| |] } {- Makes a note widget be displayed after a field. -} withNote :: Field sub master v -> GWidget sub master () -> Field sub master v withNote field note = field { fieldView = newview } where newview theId name attrs val isReq = let fieldwidget = (fieldView field) theId name attrs val isReq in [whamlet|^{fieldwidget}  ^{note}|] data EnableEncryption = SharedEncryption | NoEncryption deriving (Eq) {- Adds a check box to an AForm to control encryption. -} enableEncryptionField :: RenderMessage master FormMessage => AForm sub master EnableEncryption enableEncryptionField = areq (selectFieldList choices) "Encryption" (Just SharedEncryption) where choices :: [(Text, EnableEncryption)] choices = [ ("Encrypt all data", SharedEncryption) , ("Disable encryption", NoEncryption) ] {- Generates Remote configuration for encryption. -} configureEncryption :: EnableEncryption -> (RemoteConfigKey, String) configureEncryption SharedEncryption = ("encryption", "shared") configureEncryption NoEncryption = ("encryption", "none")