Haskell Hierarchical Libraries (cgi package)Source codeContentsIndex
Network.CGI.Monad
Portabilitynon-portable
Stabilityexperimental
Maintainerbjorn@bringert.net
Contents
CGI monad class
CGI monad transformer
Error handling
Description
Internal stuff that most people shouldn't have to use. This module mostly deals with the internals of the CGIT monad transformer.
Synopsis
class Monad m => MonadCGI m where
cgiAddHeader :: HeaderName -> String -> m ()
cgiGet :: (CGIRequest -> a) -> m a
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)
throwCGI :: (MonadCGI m, MonadIO m) => Exception -> m a
catchCGI :: CGI a -> (Exception -> CGI a) -> CGI a
tryCGI :: CGI a -> CGI (Either Exception a)
handleExceptionCGI :: CGI a -> (Exception -> CGI a) -> CGI a
CGI monad class
class Monad m => MonadCGI m where
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.
Methods
cgiAddHeader :: HeaderName -> String -> m ()
Add a response header.
cgiGet :: (CGIRequest -> a) -> m a
Get something from the CGI request.
show/hide Instances
Monad m => MonadCGI (CGIT m)
(MonadTrans t, MonadCGI m, Monad (t m)) => MonadCGI (t m)
CGI monad transformer
newtype CGIT m a
The CGIT monad transformer.
Constructors
CGIT
unCGIT :: (ReaderT CGIRequest (WriterT Headers m) a)
show/hide Instances
type CGI a = CGIT IO a
A simple CGI monad with just IO.
runCGIT :: Monad m => CGIT m a -> CGIRequest -> m (Headers, a)
Run a CGI action.
Error handling
throwCGI :: (MonadCGI m, MonadIO m) => Exception -> m a
Throw an exception in a CGI monad. The monad is required to be a MonadIO, so that we can use throwIO to guarantee ordering.
catchCGI :: CGI a -> (Exception -> CGI a) -> CGI a
Catches any expection thrown by a CGI action, and uses the given exception handler if an exception is thrown.
tryCGI :: CGI a -> CGI (Either Exception a)
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 :: CGI a -> (Exception -> CGI a) -> CGI a
Deprecated version of catchCGI. Use catchCGI instead.
Produced by Haddock version 0.8