{-# LANGUAGE RecordWildCards, OverloadedStrings, QuasiQuotes #-}
module Clckwrks.Admin.SystemEmails where
import Clckwrks
import Clckwrks.Acid (GetUACCT(..), SetUACCT(..))
import Clckwrks.Admin.Template (template)
import Control.Lens ((.~), (&))
import Data.Maybe (maybe, fromMaybe)
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T
import Happstack.Authenticate.Core (Email(..), SimpleAddress(..))
import HSP.Google.Analytics (UACCT(..))
import HSP.XMLGenerator
import HSP.XML (fromStringLit)
import Language.Haskell.HSX.QQ (hsx)
import Text.Reform
import Text.Reform.Happstack
import Text.Reform.HSP.Text
systemEmailsPage :: ClckURL -> Clck ClckURL Response
systemEmailsPage :: ClckURL -> Clck ClckURL Response
systemEmailsPage ClckURL
here =
do CoreState
coreState <- GetCoreState
-> ClckT ClckURL (ServerPartT IO) (EventResult GetCoreState)
forall event (m :: * -> *).
(QueryEvent event, GetAcidState m (EventState event), Functor m,
MonadIO m, MonadState ClckState m) =>
event -> m (EventResult event)
query (GetCoreState
-> ClckT ClckURL (ServerPartT IO) (EventResult GetCoreState))
-> GetCoreState
-> ClckT ClckURL (ServerPartT IO) (EventResult GetCoreState)
forall a b. (a -> b) -> a -> b
$ GetCoreState
GetCoreState
Text
action <- URL (ClckT ClckURL (ServerPartT IO))
-> ClckT ClckURL (ServerPartT IO) Text
forall (m :: * -> *). MonadRoute m => URL m -> m Text
showURL URL (ClckT ClckURL (ServerPartT IO))
ClckURL
here
String
-> ()
-> GenChildList (ClckT ClckURL (ServerPartT IO))
-> Clck ClckURL Response
forall (m :: * -> *) url headers body.
(Happstack m, EmbedAsChild (ClckT url m) headers,
EmbedAsChild (ClckT url m) body) =>
String -> headers -> body -> ClckT url m Response
template String
"Edit Settings" () (GenChildList (ClckT ClckURL (ServerPartT IO))
-> Clck ClckURL Response)
-> GenChildList (ClckT ClckURL (ServerPartT IO))
-> Clck ClckURL Response
forall a b. (a -> b) -> a -> b
$ [hsx|
<%>
<% reform (form action) "ss" updateSettings Nothing (editSettingsForm coreState) %>
</%> |]
where
updateSettings :: CoreState -> Clck ClckURL Response
updateSettings :: CoreState -> Clck ClckURL Response
updateSettings CoreState
coreState =
do SetCoreState
-> ClckT ClckURL (ServerPartT IO) (EventResult SetCoreState)
forall event (m :: * -> *).
(UpdateEvent event, GetAcidState m (EventState event), Functor m,
MonadIO m, MonadState ClckState m) =>
event -> m (EventResult event)
update (CoreState -> SetCoreState
SetCoreState CoreState
coreState)
URL (ClckT ClckURL (ServerPartT IO)) -> Clck ClckURL Response
forall (m :: * -> *).
(MonadRoute m, FilterMonad Response m) =>
URL m -> m Response
seeOtherURL URL (ClckT ClckURL (ServerPartT IO))
ClckURL
here
editSettingsForm :: CoreState -> ClckForm ClckURL CoreState
editSettingsForm :: CoreState -> ClckForm ClckURL CoreState
editSettingsForm c :: CoreState
c@CoreState{Bool
Maybe String
Maybe Text
Maybe SimpleAddress
Maybe UACCT
(String, Int64, Int64, Int64)
_coreBodyPolicy :: CoreState -> (String, Int64, Int64, Int64)
_coreEnableOpenId :: CoreState -> Bool
_coreSendmailPath :: CoreState -> Maybe String
_coreReplyToAddress :: CoreState -> Maybe SimpleAddress
_coreFromAddress :: CoreState -> Maybe SimpleAddress
_coreLoginRedirect :: CoreState -> Maybe Text
_coreRootRedirect :: CoreState -> Maybe Text
_coreUACCT :: CoreState -> Maybe UACCT
_coreSiteName :: CoreState -> Maybe Text
_coreBodyPolicy :: (String, Int64, Int64, Int64)
_coreEnableOpenId :: Bool
_coreSendmailPath :: Maybe String
_coreReplyToAddress :: Maybe SimpleAddress
_coreFromAddress :: Maybe SimpleAddress
_coreLoginRedirect :: Maybe Text
_coreRootRedirect :: Maybe Text
_coreUACCT :: Maybe UACCT
_coreSiteName :: Maybe Text
..} =
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divHorizontal (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
forall a b. (a -> b) -> a -> b
$
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
forall (m :: * -> *) (x :: * -> *) c input error proof a.
(Monad m, Functor m, XMLGenerator x, StringType x ~ Text,
EmbedAsChild x c) =>
Form m input error c proof a
-> Form m input error [XMLGenT x (XMLType x)] proof a
fieldset (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
forall a b. (a -> b) -> a -> b
$
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> CoreState
modifyCoreState (Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> CoreState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$
(Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (m :: * -> *) (x :: * -> *) input error.
(Monad m, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId), EmbedAsChild x Text) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () ()
labelText Text
"From: address" Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> [Attr Text Text]
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
Functor m) =>
Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
`setAttrs` [(Text
"class"Text -> Text -> Attr Text Text
forall n a. n -> a -> Attr n a
:=Text
"control-label") :: Attr Text Text]) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) view input error proof a.
(Monad m, Monoid view) =>
Form m input error view () ()
-> Form m input error view proof a
-> Form m input error view proof a
++>
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls (Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId),
EmbedAsAttr x (Attr Text Text)) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputText (Text -> (SimpleAddress -> Text) -> Maybe SimpleAddress -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty (Email -> Text
_unEmail (Email -> Text)
-> (SimpleAddress -> Email) -> SimpleAddress -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleAddress -> Email
_saEmail) Maybe SimpleAddress
_coreFromAddress)) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> (Text -> Either ClckFormError (Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) input error view anyProof a b.
Monad m =>
Form m input error view anyProof a
-> (a -> Either error b) -> Form m input error view () b
`transformEither` Text -> Either ClckFormError (Maybe Text)
toMaybe))
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> Maybe Text -> Maybe Text -> CoreState)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$
(Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (m :: * -> *) (x :: * -> *) c input error.
(Monad m, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId), EmbedAsChild x c) =>
c -> Form m input error [XMLGenT x (XMLType x)] () ()
label (Text
"From: name" :: Text) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> [Attr Text Text]
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
Functor m) =>
Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
`setAttrs` [(Text
"class"Text -> Text -> Attr Text Text
forall n a. n -> a -> Attr n a
:=Text
"control-label") :: Attr Text Text]) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) view input error proof a.
(Monad m, Monoid view) =>
Form m input error view () ()
-> Form m input error view proof a
-> Form m input error view proof a
++>
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls (Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId),
EmbedAsAttr x (Attr Text Text)) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputText (Text -> (SimpleAddress -> Text) -> Maybe SimpleAddress -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text)
-> (SimpleAddress -> Maybe Text) -> SimpleAddress -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleAddress -> Maybe Text
_saName) Maybe SimpleAddress
_coreFromAddress)) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> (Text -> Either ClckFormError (Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) input error view anyProof a b.
Monad m =>
Form m input error view anyProof a
-> (a -> Either error b) -> Form m input error view () b
`transformEither` Text -> Either ClckFormError (Maybe Text)
toMaybe))
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> Maybe Text -> Maybe Text -> CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> Maybe Text -> CoreState)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$
(Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (m :: * -> *) (x :: * -> *) c input error.
(Monad m, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId), EmbedAsChild x c) =>
c -> Form m input error [XMLGenT x (XMLType x)] () ()
label (Text
"Reply-to: address" :: Text) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> [Attr Text Text]
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
Functor m) =>
Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
`setAttrs` [(Text
"class"Text -> Text -> Attr Text Text
forall n a. n -> a -> Attr n a
:=Text
"control-label") :: Attr Text Text]) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) view input error proof a.
(Monad m, Monoid view) =>
Form m input error view () ()
-> Form m input error view proof a
-> Form m input error view proof a
++>
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls (Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId),
EmbedAsAttr x (Attr Text Text)) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputText (Text -> (SimpleAddress -> Text) -> Maybe SimpleAddress -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty (Email -> Text
_unEmail (Email -> Text)
-> (SimpleAddress -> Email) -> SimpleAddress -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleAddress -> Email
_saEmail) Maybe SimpleAddress
_coreReplyToAddress)) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> (Text -> Either ClckFormError (Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) input error view anyProof a b.
Monad m =>
Form m input error view anyProof a
-> (a -> Either error b) -> Form m input error view () b
`transformEither` Text -> Either ClckFormError (Maybe Text)
toMaybe))
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> Maybe Text -> CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> CoreState)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$
(Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (m :: * -> *) (x :: * -> *) c input error.
(Monad m, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId), EmbedAsChild x c) =>
c -> Form m input error [XMLGenT x (XMLType x)] () ()
label (Text
"Reply-to: name" :: Text) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> [Attr Text Text]
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
Functor m) =>
Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
`setAttrs` [(Text
"class"Text -> Text -> Attr Text Text
forall n a. n -> a -> Attr n a
:=Text
"control-label") :: Attr Text Text]) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) view input error proof a.
(Monad m, Monoid view) =>
Form m input error view () ()
-> Form m input error view proof a
-> Form m input error view proof a
++>
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls (Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId),
EmbedAsAttr x (Attr Text Text)) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputText (Text -> (SimpleAddress -> Text) -> Maybe SimpleAddress -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text)
-> (SimpleAddress -> Maybe Text) -> SimpleAddress -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleAddress -> Maybe Text
_saName) Maybe SimpleAddress
_coreReplyToAddress)) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> (Text -> Either ClckFormError (Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) input error view anyProof a b.
Monad m =>
Form m input error view anyProof a
-> (a -> Either error b) -> Form m input error view () b
`transformEither` Text -> Either ClckFormError (Maybe Text)
toMaybe))
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text -> CoreState)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$
(Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (m :: * -> *) (x :: * -> *) input error.
(Monad m, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId), EmbedAsChild x Text) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () ()
labelText Text
"sendmail path" Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> [Attr Text Text]
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
Functor m) =>
Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
`setAttrs` [(Text
"class"Text -> Text -> Attr Text Text
forall n a. n -> a -> Attr n a
:=Text
"control-label") :: Attr Text Text]) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
()
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) view input error proof a.
(Monad m, Monoid view) =>
Form m input error view () ()
-> Form m input error view proof a
-> Form m input error view proof a
++>
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls (Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId),
EmbedAsAttr x (Attr Text Text)) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () Text
inputText (Text -> (String -> Text) -> Maybe String -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty String -> Text
T.pack Maybe String
_coreSendmailPath)) Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
Text
-> (Text -> Either ClckFormError (Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) input error view anyProof a b.
Monad m =>
Form m input error view anyProof a
-> (a -> Either error b) -> Form m input error view () b
`transformEither` Text -> Either ClckFormError (Maybe Text)
toMaybe)))
Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
CoreState
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
(Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$ Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall input error proof a.
Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls (Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text))
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (m :: * -> *) input error (x :: * -> *).
(Monad m, FormInput input, FormError error,
ErrorInputType error ~ input, XMLGenerator x, StringType x ~ Text,
EmbedAsAttr x (Attr Text FormId),
EmbedAsAttr x (Attr Text Text)) =>
Text -> Form m input error [XMLGenT x (XMLType x)] () (Maybe Text)
inputSubmit Text
"Update" Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
-> [Attr Text Text]
-> Form
(ClckT ClckURL (ServerPartT IO))
[Input]
ClckFormError
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
()
(Maybe Text)
forall (x :: * -> *) attr (m :: * -> *) input error proof a.
(EmbedAsAttr x attr, XMLGenerator x, StringType x ~ Text, Monad m,
Functor m) =>
Form m input error [XMLGenT x (XMLType x)] proof a
-> attr -> Form m input error [XMLGenT x (XMLType x)] proof a
`setAttrs` [(Text
"class" Text -> Text -> Attr Text Text
forall n a. n -> a -> Attr n a
:= Text
"btn") :: Attr Text Text])
where
divHorizontal :: Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divHorizontal = ([XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
-> [XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))])
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
forall (m :: * -> *) view view' input error proof a.
(Monad m, Functor m) =>
(view -> view')
-> Form m input error view proof a
-> Form m input error view' proof a
mapView (\[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
xml -> [[hsx| <div class="form-horizontal"><% xml %></div>|]])
divControlGroup :: Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControlGroup = ([XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
-> [XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))])
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
forall (m :: * -> *) view view' input error proof a.
(Monad m, Functor m) =>
(view -> view')
-> Form m input error view proof a
-> Form m input error view' proof a
mapView (\[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
xml -> [[hsx| <div class="control-group"><% xml %></div>|]])
divControls :: Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
divControls = ([XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
-> [XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))])
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
-> Form
(ClckT ClckURL (ServerPartT IO))
input
error
[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
proof
a
forall (m :: * -> *) view view' input error proof a.
(Monad m, Functor m) =>
(view -> view')
-> Form m input error view proof a
-> Form m input error view' proof a
mapView (\[XMLGenT
(ClckT ClckURL (ServerPartT IO))
(XMLType (ClckT ClckURL (ServerPartT IO)))]
xml -> [[hsx| <div class="controls"><% xml %></div>|]])
toMaybe :: Text -> Either ClckFormError (Maybe Text)
toMaybe :: Text -> Either ClckFormError (Maybe Text)
toMaybe Text
txt =
if Text -> Bool
T.null Text
txt
then Maybe Text -> Either ClckFormError (Maybe Text)
forall a b. b -> Either a b
Right (Maybe Text -> Either ClckFormError (Maybe Text))
-> Maybe Text -> Either ClckFormError (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Maybe Text
forall a. Maybe a
Nothing
else Maybe Text -> Either ClckFormError (Maybe Text)
forall a b. b -> Either a b
Right (Maybe Text -> Either ClckFormError (Maybe Text))
-> Maybe Text -> Either ClckFormError (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
txt
modifyCoreState :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> CoreState
modifyCoreState Maybe Text
mFromAddress Maybe Text
mFromName Maybe Text
mReplyToAddress Maybe Text
mReplyToName Maybe Text
mSendmailPath =
CoreState
c CoreState -> (CoreState -> CoreState) -> CoreState
forall a b. a -> (a -> b) -> b
& (Maybe SimpleAddress -> Identity (Maybe SimpleAddress))
-> CoreState -> Identity CoreState
Lens' CoreState (Maybe SimpleAddress)
coreFromAddress ((Maybe SimpleAddress -> Identity (Maybe SimpleAddress))
-> CoreState -> Identity CoreState)
-> Maybe SimpleAddress -> CoreState -> CoreState
forall s t a b. ASetter s t a b -> b -> s -> t
.~
case Maybe Text
mFromAddress of
Maybe Text
Nothing -> Maybe SimpleAddress
forall a. Maybe a
Nothing
(Just Text
addr) -> SimpleAddress -> Maybe SimpleAddress
forall a. a -> Maybe a
Just (Maybe Text -> Email -> SimpleAddress
SimpleAddress Maybe Text
mFromName (Text -> Email
Email Text
addr))
CoreState -> (CoreState -> CoreState) -> CoreState
forall a b. a -> (a -> b) -> b
& (Maybe SimpleAddress -> Identity (Maybe SimpleAddress))
-> CoreState -> Identity CoreState
Lens' CoreState (Maybe SimpleAddress)
coreReplyToAddress ((Maybe SimpleAddress -> Identity (Maybe SimpleAddress))
-> CoreState -> Identity CoreState)
-> Maybe SimpleAddress -> CoreState -> CoreState
forall s t a b. ASetter s t a b -> b -> s -> t
.~
case Maybe Text
mReplyToAddress of
Maybe Text
Nothing -> Maybe SimpleAddress
forall a. Maybe a
Nothing
(Just Text
addr) -> SimpleAddress -> Maybe SimpleAddress
forall a. a -> Maybe a
Just (Maybe Text -> Email -> SimpleAddress
SimpleAddress Maybe Text
mReplyToName (Text -> Email
Email Text
addr))
CoreState -> (CoreState -> CoreState) -> CoreState
forall a b. a -> (a -> b) -> b
& (Maybe String -> Identity (Maybe String))
-> CoreState -> Identity CoreState
Lens' CoreState (Maybe String)
coreSendmailPath ((Maybe String -> Identity (Maybe String))
-> CoreState -> Identity CoreState)
-> Maybe String -> CoreState -> CoreState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (Text -> String
T.unpack (Text -> String) -> Maybe Text -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
mSendmailPath)