Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
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 ...
Synopsis
- newtype ControllerT s (m :: Type -> Type) a = ControllerT {
- runController :: s -> Request -> m (Either Response a, s)
- hoistEither :: forall (m :: Type -> Type) a s. Monad m => Either Response a -> ControllerT s m a
- request :: forall (m :: Type -> Type) s. Monad m => ControllerT s m Request
- localRequest :: forall (m :: Type -> Type) s a. Monad m => (Request -> Request) -> ControllerT s m a -> ControllerT s m a
- controllerState :: forall (m :: Type -> Type) s. Monad m => ControllerT s m s
- putState :: forall (m :: Type -> Type) s. Monad m => s -> ControllerT s m ()
- controllerApp :: Monad m => s -> ControllerT s m a -> SimpleApplication m
- respond :: forall (m :: Type -> Type) s a. Monad m => Response -> ControllerT s m a
- fromApp :: Monad m => (Request -> m Response) -> ControllerT s m ()
- routeHost :: forall (m :: Type -> Type) s a. Monad m => ByteString -> ControllerT s m a -> ControllerT s m ()
- routeTop :: forall (m :: Type -> Type) s a. Monad m => ControllerT s m a -> ControllerT s m ()
- routeMethod :: forall (m :: Type -> Type) s a. Monad m => StdMethod -> ControllerT s m a -> ControllerT s m ()
- routeAccept :: forall (m :: Type -> Type) s a. Monad m => ByteString -> ControllerT s m a -> ControllerT s m ()
- routePattern :: forall (m :: Type -> Type) s a. Monad m => Text -> ControllerT s m a -> ControllerT s m ()
- routeName :: forall (m :: Type -> Type) s a. Monad m => Text -> ControllerT s m a -> ControllerT s m ()
- routeVar :: forall (m :: Type -> Type) s a. Monad m => Text -> ControllerT s m a -> ControllerT s m ()
- queryParam :: forall (m :: Type -> Type) a s. (Monad m, Parseable a) => ByteString -> ControllerT s m (Maybe a)
- queryParam' :: forall (m :: Type -> Type) a s. (Monad m, Parseable a) => ByteString -> ControllerT s m a
- queryParams :: forall (m :: Type -> Type) a s. (Monad m, Parseable a) => ByteString -> ControllerT s m [a]
- class Parseable a where
- parse :: ByteString -> a
- readQueryParam :: forall (m :: Type -> Type) a s. (Monad m, Read a) => ByteString -> ControllerT s m (Maybe a)
- readQueryParam' :: forall (m :: Type -> Type) a s. (Monad m, Read a) => ByteString -> ControllerT s m a
- readQueryParams :: forall (m :: Type -> Type) a s. (Monad m, Read a) => ByteString -> ControllerT s m [a]
- readParamValue :: forall (m :: Type -> Type) a s. (Monad m, Read a) => ByteString -> Text -> ControllerT s m a
- requestHeader :: forall (m :: Type -> Type) s. Monad m => HeaderName -> ControllerT s m (Maybe ByteString)
- redirectBack :: forall (m :: Type -> Type) s. Monad m => ControllerT s m ()
- redirectBackOr :: forall (m :: Type -> Type) s. Monad m => Response -> ControllerT s m ()
- type SimpleApplication (m :: Type -> Type) = Request -> m Response
- type SimpleMiddleware (m :: Type -> Type) = SimpleApplication m -> SimpleApplication m
- guard :: forall (m :: Type -> Type) s a. Monad m => Bool -> ControllerT s m a -> ControllerT s m ()
- guardM :: forall (m :: Type -> Type) s a. Monad m => ControllerT s m Bool -> ControllerT s m a -> ControllerT s m ()
- guardReq :: forall (m :: Type -> Type) s a. Monad m => (Request -> Bool) -> ControllerT s m a -> ControllerT s m ()
- data ControllerException = ControllerException String
- err :: forall s (m :: Type -> Type) a. String -> ControllerT s m a
Documentation
newtype ControllerT s (m :: Type -> Type) 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 respond
ing with a Response
.
Constructors
ControllerT | |
Fields
|
Instances
hoistEither :: forall (m :: Type -> Type) a s. Monad m => Either Response a -> ControllerT s m a Source #
request :: forall (m :: Type -> Type) s. Monad m => ControllerT s m Request Source #
Extract the request
localRequest :: forall (m :: Type -> Type) s a. Monad m => (Request -> Request) -> ControllerT s m a -> ControllerT s m a Source #
Modify the request for the given computation
controllerState :: forall (m :: Type -> Type) s. Monad m => ControllerT s m s Source #
Extract the application-specific state
controllerApp :: Monad m => s -> ControllerT s m a -> SimpleApplication m Source #
Convert the controller into an Application
respond :: forall (m :: Type -> Type) s a. Monad m => Response -> ControllerT s m a Source #
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 :: forall (m :: Type -> Type) s a. 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 :: forall (m :: Type -> Type) s a. Monad m => ControllerT s m a -> ControllerT s m () Source #
routeMethod :: forall (m :: Type -> Type) s a. Monad m => StdMethod -> ControllerT s m a -> ControllerT s m () Source #
routeAccept :: forall (m :: Type -> Type) s a. Monad m => ByteString -> ControllerT s m a -> ControllerT s m () Source #
Matches if the request's Content-Type exactly matches the given string
routePattern :: forall (m :: Type -> Type) s a. 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 :: forall (m :: Type -> Type) s a. Monad m => Text -> ControllerT s m a -> ControllerT s m () Source #
Matches if the first directory in the path matches the given ByteString
routeVar :: forall (m :: Type -> Type) s a. 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
:: forall (m :: Type -> Type) a s. (Monad m, Parseable a) | |
=> ByteString | Parameter name |
-> ControllerT s m (Maybe a) |
Looks up the parameter name in the request's query string and returns the
Parseable
value or Nothing
.
For example, for a request with query string: "?foo=bar&baz=7",
queryParam "foo"
would return Just "bar"
, but
queryParam "zap"
would return Nothing
.
queryParam' :: forall (m :: Type -> Type) a s. (Monad m, Parseable a) => ByteString -> ControllerT s m a Source #
Like queryParam
, but throws an exception if the parameter is not present.
queryParams :: forall (m :: Type -> Type) a s. (Monad m, Parseable a) => ByteString -> ControllerT s m [a] Source #
Selects all values with the given parameter name
class Parseable a where Source #
The class of types into which query parameters may be converted
Methods
parse :: ByteString -> a Source #
Instances
Parseable ByteString Source # | |
Defined in Web.Simple.Controller.Trans Methods parse :: ByteString -> ByteString Source # | |
Parseable Text Source # | |
Defined in Web.Simple.Controller.Trans Methods parse :: ByteString -> Text Source # | |
Parseable String Source # | |
Defined in Web.Simple.Controller.Trans Methods parse :: ByteString -> String Source # |
Arguments
:: forall (m :: Type -> Type) a s. (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
:: forall (m :: Type -> Type) a s. (Monad m, Read a) | |
=> ByteString | Parameter name |
-> ControllerT s m a |
Like readQueryParam
, but throws an exception if the parameter is not present.
Arguments
:: forall (m :: Type -> Type) a s. (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 :: forall (m :: Type -> Type) a s. (Monad m, Read a) => ByteString -> Text -> ControllerT s m a Source #
requestHeader :: forall (m :: Type -> Type) s. 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 :: forall (m :: Type -> Type) s. Monad m => ControllerT s m () Source #
Redirect back to the referer. If the referer header is not present
redirect to root (i.e., /
).
Arguments
:: forall (m :: Type -> Type) s. 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 :: Type -> Type) = Request -> m Response Source #
Like Application
, but with m
as the underlying monad
type SimpleMiddleware (m :: Type -> Type) = SimpleApplication m -> SimpleApplication m Source #
Like Application
, but with m
as the underlying monad
guard :: forall (m :: Type -> Type) s a. Monad m => Bool -> ControllerT s m a -> ControllerT s m () Source #
guardM :: forall (m :: Type -> Type) s a. Monad m => ControllerT s m Bool -> ControllerT s m a -> ControllerT s m () Source #
guardReq :: forall (m :: Type -> Type) s a. Monad m => (Request -> Bool) -> ControllerT s m a -> ControllerT s m () Source #
data ControllerException Source #
Constructors
ControllerException String |
Instances
Exception ControllerException Source # | |
Defined in Web.Simple.Controller.Trans Methods toException :: ControllerException -> SomeException # fromException :: SomeException -> Maybe ControllerException # | |
Show ControllerException Source # | |
Defined in Web.Simple.Controller.Trans Methods showsPrec :: Int -> ControllerException -> ShowS # show :: ControllerException -> String # showList :: [ControllerException] -> ShowS # |
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.
Route
s 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?"