Copyright | (c) Bjorn Bringert 2006 |
---|---|
License | BSD-style |
Maintainer | John Chee <cheecheeo@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell98 |
Internal stuff that most people shouldn't have to use. This module mostly deals with the internals of the CGIT monad transformer.
- class Monad m => MonadCGI m where
- newtype CGIT m a = CGIT {
- unCGIT :: ReaderT CGIRequest (WriterT Headers m) a
- type CGI a = CGIT IO a
- runCGIT :: Monad m => CGIT m a -> CGIRequest -> m (Headers, a)
- data CGIRequest = CGIRequest {
- cgiVars :: Map String String
- cgiInputs :: [(String, Input)]
- cgiRequestBody :: ByteString
- throwCGI :: (MonadCGI m, MonadThrow m) => SomeException -> m a
- catchCGI :: (MonadCGI m, MonadCatch m) => m a -> (SomeException -> m a) -> m a
- tryCGI :: (Functor m, MonadCGI m, MonadCatch m) => m a -> m (Either SomeException a)
- handleExceptionCGI :: (MonadCGI m, MonadCatch m) => m a -> (SomeException -> m a) -> m a
CGI monad class
class Monad m => MonadCGI m where Source #
The class of CGI monads. Most CGI actions can be run in any monad which is an instance of this class, which means that you can use your own monad transformers to add extra functionality.
cgiAddHeader :: HeaderName -> String -> m () Source #
Add a response header.
cgiGet :: (CGIRequest -> a) -> m a Source #
Get something from the CGI request.
CGI monad transformer
The CGIT monad transformer.
MonadTrans CGIT Source # | |
MonadCatch m => MonadError SomeException (CGIT m) Source # | |
Monad m => Monad (CGIT m) Source # | |
(Functor m, Monad m) => Functor (CGIT m) Source # | |
(Applicative m, Monad m) => Applicative (CGIT m) Source # | |
MonadIO m => MonadIO (CGIT m) Source # | |
MonadThrow m => MonadThrow (CGIT m) Source # | |
MonadCatch m => MonadCatch (CGIT m) Source # | |
MonadMask m => MonadMask (CGIT m) Source # | |
Monad m => MonadCGI (CGIT m) Source # | |
Request info
data CGIRequest Source #
The input to a CGI action.
CGIRequest | |
|
Error handling
throwCGI :: (MonadCGI m, MonadThrow m) => SomeException -> m a Source #
Throw an exception in a CGI monad. The monad is required to be
a MonadThrow
, so that we can use throwM
to guarantee ordering.
catchCGI :: (MonadCGI m, MonadCatch m) => m a -> (SomeException -> m a) -> m a Source #
Catches any expection thrown by a CGI action, and uses the given exception handler if an exception is thrown.
tryCGI :: (Functor m, MonadCGI m, MonadCatch m) => m a -> m (Either SomeException a) Source #
Catches any exception thrown by an CGI action, and returns either the exception, or if no exception was raised, the result of the action.
handleExceptionCGI :: (MonadCGI m, MonadCatch m) => m a -> (SomeException -> m a) -> m a Source #