simple-0.7.0.1: A minimalist web framework for the WAI server interface

Safe HaskellNone

Web.Simple.Controller

Contents

Description

Controller 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:

    myController = do
      ...
      if badLogin then
        redirectBack
        else
          ...

Synopsis

Example

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 :: Controller () ()
  mainAction = ...

signinForm :: Controller () ()
  signinForm req = ...

login :: Controller () ()
  login = ...

updateProfile :: Controller () ()
  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?"

newtype Controller r a Source

The Controller Monad is both a State-like monad which, when run, computes either a Response or a result. Within the Controller Monad, the remainder of the computation can be short-circuited by responding with a Response.

Constructors

Controller (ControllerState r -> IO (Either Response a, ControllerState r)) 

controllerApp :: r -> Controller r a -> ApplicationSource

Convert the controller into an Application

controllerState :: Controller r rSource

Extract the application-specific state

request :: Controller r RequestSource

Extract the request

localRequest :: (Request -> Request) -> Controller r a -> Controller r aSource

Modify the request for the given computation

respond :: Response -> Controller r aSource

Provide a response

respond r >>= f === respond r

requestHeader :: HeaderName -> Controller r (Maybe ByteString)Source

Returns the value of the given request header or Nothing if it is not present in the HTTP request.

Common Routes

routeHost :: ByteString -> Controller r a -> Controller r ()Source

Matches on the hostname from the Request. The route only succeeds on exact matches.

routeTop :: Controller r a -> Controller r ()Source

Matches if the path is empty.

Note that this route checks that pathInfo is empty, so it works as expected in nested contexts that have popped components from the pathInfo list.

routeMethod :: StdMethod -> Controller r a -> Controller r ()Source

Matches on the HTTP request method (e.g. GET, POST, PUT)

routeAccept :: ByteString -> Controller r a -> Controller r ()Source

Matches if the request's Content-Type exactly matches the given string

routePattern :: ByteString -> Controller r a -> Controller r ()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 :: ByteString -> Controller r a -> Controller r ()Source

Matches if the first directory in the path matches the given ByteString

routeVar :: ByteString -> Controller r a -> Controller r ()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.

Inspecting query

class Parseable a Source

The class of types into which query parameters may be converted

queryParamSource

Arguments

:: Parseable a 
=> ByteString

Parameter name

-> Controller r (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' :: Parseable a => ByteString -> Controller r aSource

Like queryParam, but throws an exception if the parameter is not present.

queryParams :: Parseable a => ByteString -> Controller r [a]Source

Selects all values with the given parameter name

readQueryParamSource

Arguments

:: Read a 
=> ByteString

Parameter name

-> Controller r (Maybe a) 

Like queryParam, but further processes the parameter value with read. If that conversion fails, an exception is thrown.

readQueryParam'Source

Arguments

:: Read a 
=> ByteString

Parameter name

-> Controller r a 

Like readQueryParam, but throws an exception if the parameter is not present.

readQueryParamsSource

Arguments

:: Read a 
=> ByteString

Parameter name

-> Controller r [a] 

Like queryParams, but further processes the parameter values with read. If any read-conversion fails, an exception is thrown.

parseForm :: Controller r ([Param], [(ByteString, FileInfo ByteString)])Source

Parses a HTML form from the request body. It returns a list of Params as well as a list of Files, which are pairs mapping the name of a file form field to a FileInfo pointing to a temporary file with the contents of the upload.

   myController = do
     (prms, files) <- parseForm
     let mPicFile = lookup "profile_pic" files
     case mPicFile of
       Just (picFile) -> do
         sourceFile (fileContent picFile) $$
           sinkFile ("images/" ++ (fileName picFile))
         respond $ redirectTo "/"
       Nothing -> redirectBack

Redirection via referrer

redirectBack :: Controller r ()Source

Redirect back to the referer. If the referer header is not present redirect to root (i.e., /).

redirectBackOrSource

Arguments

:: Response

Fallback response

-> Controller r () 

Redirect back to the referer. If the referer header is not present fallback on the given Response.

Exception handling

Integrating other WAI components

class ToApplication r whereSource

The class of types that can be converted to an Application

Methods

toApp :: r -> ApplicationSource

fromApp :: ToApplication a => a -> Controller r ()Source

Lift an application to a controller

Low-level utilities

body :: Controller r ByteStringSource

Reads and returns the body of the HTTP request.