| Safe Haskell | Trustworthy |
|---|
Web.Simple.Controller.Trans
Description
ControllerT provides a convenient syntax for writting Application
code as a Monadic action with access to an HTTP request as well as app
specific data (e.g. a database connection pool, app configuration etc.)
This module also defines some
helper functions that leverage this feature. For example, redirectBack
reads the underlying request to extract the referer and returns a redirect
response:
myControllerT = do
...
if badLogin then
redirectBack
else
...
- newtype ControllerT s m a = ControllerT {
- runController :: s -> Request -> m (Either Response a, s)
- hoistEither :: Monad m => Either Response a -> ControllerT s m a
- request :: Monad m => ControllerT s m Request
- localRequest :: Monad m => (Request -> Request) -> ControllerT s m a -> ControllerT s m a
- controllerState :: Monad m => ControllerT s m s
- putState :: Monad m => s -> ControllerT s m ()
- controllerApp :: Monad m => s -> ControllerT s m a -> SimpleApplication m
- respond :: Monad m => Response -> ControllerT s m a
- fromApp :: Monad m => (Request -> m Response) -> ControllerT s m ()
- routeHost :: Monad m => ByteString -> ControllerT s m a -> ControllerT s m ()
- routeTop :: Monad m => ControllerT s m a -> ControllerT s m ()
- routeMethod :: Monad m => StdMethod -> ControllerT s m a -> ControllerT s m ()
- routeAccept :: Monad m => ByteString -> ControllerT s m a -> ControllerT s m ()
- routePattern :: Monad m => Text -> ControllerT s m a -> ControllerT s m ()
- routeName :: Monad m => Text -> ControllerT s m a -> ControllerT s m ()
- routeVar :: Monad m => Text -> ControllerT s m a -> ControllerT s m ()
- queryParam :: (Monad m, Parseable a) => ByteString -> ControllerT s m (Maybe a)
- queryParam' :: (Monad m, Parseable a) => ByteString -> ControllerT s m a
- queryParams :: (Monad m, Parseable a) => ByteString -> ControllerT s m [a]
- class Parseable a where
- parse :: ByteString -> a
- readQueryParam :: (Monad m, Read a) => ByteString -> ControllerT s m (Maybe a)
- readQueryParam' :: (Monad m, Read a) => ByteString -> ControllerT s m a
- readQueryParams :: (Monad m, Read a) => ByteString -> ControllerT s m [a]
- readParamValue :: (Monad m, Read a) => ByteString -> Text -> ControllerT s m a
- requestHeader :: Monad m => HeaderName -> ControllerT s m (Maybe ByteString)
- redirectBack :: Monad m => ControllerT s m ()
- redirectBackOr :: Monad m => Response -> ControllerT s m ()
- type SimpleApplication m = Request -> m Response
- type SimpleMiddleware m = SimpleApplication m -> SimpleApplication m
- guard :: Monad m => Bool -> ControllerT s m a -> ControllerT s m ()
- guardM :: Monad m => ControllerT s m Bool -> ControllerT s m a -> ControllerT s m ()
- guardReq :: Monad m => (Request -> Bool) -> ControllerT s m a -> ControllerT s m ()
- data ControllerException = ControllerException String
- err :: String -> ControllerT s m a
Documentation
newtype ControllerT s m a Source
The ControllerT Monad is both a State-like monad which, when run, computes
either a Response or a result. Within the ControllerT Monad, the remainder
of the computation can be short-circuited by responding with a Response.
Constructors
| ControllerT | |
Fields
| |
Instances
| Monad m => MonadReader Request (ControllerT s m) | |
| Monad m => MonadState s (ControllerT s m) | |
| MonadTrans (ControllerT s) | |
| Monad m => Monad (ControllerT s m) | |
| Functor m => Functor (ControllerT s m) | |
| Monad m => MonadPlus (ControllerT s m) | |
| (Monad m, Functor m) => Applicative (ControllerT s m) | |
| (Functor m, Monad m) => Alternative (ControllerT s m) | |
| MonadPeelIO (ControllerT s IO) | |
| MonadIO m => MonadIO (ControllerT s m) |
hoistEither :: Monad m => Either Response a -> ControllerT s m aSource
request :: Monad m => ControllerT s m RequestSource
Extract the request
localRequest :: Monad m => (Request -> Request) -> ControllerT s m a -> ControllerT s m aSource
Modify the request for the given computation
controllerState :: Monad m => ControllerT s m sSource
Extract the application-specific state
putState :: Monad m => s -> ControllerT s m ()Source
controllerApp :: Monad m => s -> ControllerT s m a -> SimpleApplication mSource
Convert the controller into an Application
respond :: Monad m => Response -> ControllerT s m aSource
Provide a response
respond r >>= f === respond r
fromApp :: Monad m => (Request -> m Response) -> ControllerT s m ()Source
Lift an application to a controller
routeHost :: Monad m => ByteString -> ControllerT s m a -> ControllerT s m ()Source
Matches on the hostname from the Request. The route only succeeds on
exact matches.
routeTop :: Monad m => ControllerT s m a -> ControllerT s m ()Source
routeMethod :: Monad m => StdMethod -> ControllerT s m a -> ControllerT s m ()Source
routeAccept :: Monad m => ByteString -> ControllerT s m a -> ControllerT s m ()Source
Matches if the request's Content-Type exactly matches the given string
routePattern :: Monad m => Text -> ControllerT s m a -> ControllerT s m ()Source
Routes the given URL pattern. Patterns can include
directories as well as variable patterns (prefixed with :) to be added
to queryString (see routeVar)
- /posts/:id
- /posts/:id/new
- /:date/posts/:category/new
routeName :: Monad m => Text -> ControllerT s m a -> ControllerT s m ()Source
Matches if the first directory in the path matches the given ByteString
routeVar :: Monad m => Text -> ControllerT s m a -> ControllerT s m ()Source
Always matches if there is at least one directory in pathInfo but and
adds a parameter to queryString where the key is the first parameter and
the value is the directory consumed from the path.
Arguments
| :: (Monad m, Parseable a) | |
| => ByteString | Parameter name |
| -> ControllerT s m (Maybe a) |
queryParam' :: (Monad m, Parseable a) => ByteString -> ControllerT s m aSource
Like queryParam, but throws an exception if the parameter is not present.
queryParams :: (Monad m, Parseable a) => ByteString -> ControllerT s m [a]Source
Selects all values with the given parameter name
The class of types into which query parameters may be converted
Methods
parse :: ByteString -> aSource
Arguments
| :: (Monad m, Read a) | |
| => ByteString | Parameter name |
| -> ControllerT s m (Maybe a) |
Like queryParam, but further processes the parameter value with read.
If that conversion fails, an exception is thrown.
Arguments
| :: (Monad m, Read a) | |
| => ByteString | Parameter name |
| -> ControllerT s m a |
Like readQueryParam, but throws an exception if the parameter is not present.
Arguments
| :: (Monad m, Read a) | |
| => ByteString | Parameter name |
| -> ControllerT s m [a] |
Like queryParams, but further processes the parameter values with read.
If any read-conversion fails, an exception is thrown.
readParamValue :: (Monad m, Read a) => ByteString -> Text -> ControllerT s m aSource
requestHeader :: Monad m => HeaderName -> ControllerT s m (Maybe ByteString)Source
Returns the value of the given request header or Nothing if it is not
present in the HTTP request.
redirectBack :: Monad m => ControllerT s m ()Source
Redirect back to the referer. If the referer header is not present
redirect to root (i.e., /).
Arguments
| :: Monad m | |
| => Response | Fallback response |
| -> ControllerT s m () |
Redirect back to the referer. If the referer header is not present
fallback on the given Response.
type SimpleApplication m = Request -> m ResponseSource
Like Application, but with m as the underlying monad
type SimpleMiddleware m = SimpleApplication m -> SimpleApplication mSource
Like Application, but with m as the underlying monad
guard :: Monad m => Bool -> ControllerT s m a -> ControllerT s m ()Source
guardM :: Monad m => ControllerT s m Bool -> ControllerT s m a -> ControllerT s m ()Source
guardReq :: Monad m => (Request -> Bool) -> ControllerT s m a -> ControllerT s m ()Source
data ControllerException Source
Constructors
| ControllerException String |
err :: String -> ControllerT s m aSource
The most basic Routeable types are Application and Response. Reaching
either of these types marks a termination in the routing lookup. This module
exposes a monadic type Route which makes it easy to create routing logic
in a DSL-like fashion.
Routes are concatenated using the >> operator (or using do-notation).
In the end, any Routeable, including a Route is converted to an
Application and passed to the server using mkRoute:
mainAction :: ControllerT () ()
mainAction = ...
signinForm :: ControllerT () ()
signinForm req = ...
login :: ControllerT () ()
login = ...
updateProfile :: ControllerT () ()
updateProfile = ...
main :: IO ()
main = run 3000 $ controllerApp () $ do
routeTop mainAction
routeName "sessions" $ do
routeMethod GET signinForm
routeMethod POST login
routeMethod PUT $ routePattern "users/:id" updateProfile
routeAll $ responseLBS status404 [] "Are you in the right place?"