thentos-cookie-session-0.9.0: All-in-one session handling for servant-based frontends

Safe HaskellNone
LanguageHaskell2010

Servant.Missing

Synopsis

Documentation

class ThrowServantErr err where Source

Minimal complete definition

Nothing

Methods

_ServantErr :: Prism' err ServantErr Source

throwServantErr :: MonadError err m => ServantErr -> m any Source

Instances

ThrowServantErr ServantErr Source 

type MonadServantErr err m = (MonadError err m, ThrowServantErr err) Source

class ThrowError500 err where Source

Minimal complete definition

error500

Methods

error500 :: Prism' err String Source

throwError500 :: MonadError err m => String -> m b Source

Instances

ThrowError500 ServantErr Source 

type MonadError500 err m = (MonadError err m, ThrowError500 err) Source

type FormH htm html payload = Get htm html :<|> (FormReqBody :> Post htm html) Source

data FormReqBody Source

Instances

HasServer * sublayout context => HasServer * ((:>) * * FormReqBody sublayout) context Source 
type ServerT * ((:>) * * FormReqBody sublayout) m = FormData -> ServerT * sublayout m Source 

formH :: forall payload m err htm html uri. (Monad m, MonadError err m, ConvertibleStrings uri ST) => (IO :~> m) -> uri -> Form html m payload -> (payload -> m html) -> (View html -> uri -> m html) -> ServerT (FormH htm html payload) m Source

Handle a route of type FormH htm html payload. formAction is used by digestive-functors as submit path for the HTML FORM element. processor1 constructs the form, either as empty in response to a GET, or displaying validation errors in response to a POST. processor2 responds to a POST, handles the validated input values, and returns a new page displaying the result. Note that the renderer is monadic so that it can have effects (such as e.g. flushing a message queue in the session state).

formRedirectH Source

Arguments

:: (MonadIO m, MonadError ServantErr m, ConvertibleStrings uri ST, ConvertibleStrings uri SBS) 
=> uri

formAction

-> Form html m payload

processor1

-> (payload -> m uri)

processor2

-> (View html -> uri -> m html)

renderer

-> ServerT (FormH htm html payload) m 

Handle a route of type FormH htm html payload and redirect afterwards. formAction is used by digestive-functors as submit path for the HTML FORM element. processor1 constructs the form, either as empty in response to a GET, or displaying validation errors in response to a POST. processor2 responds to a POST, handles the validated input values, calculates the redirection address. Note that the renderer is monadic so that it can have effects (such as e.g. flushing a message queue in the session state).

redirect :: (MonadServantErr err m, ConvertibleStrings uri SBS) => uri -> m a Source