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

Safe HaskellTrustworthy
LanguageHaskell2010

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

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
(Applicative m, Monad m, MonadBase m m) => MonadBase m (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

liftBase :: m α -> ControllerT s m α #

MonadBaseControl m m => MonadBaseControl m (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Associated Types

type StM (ControllerT s m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ControllerT s m) m -> m a) -> ControllerT s m a #

restoreM :: StM (ControllerT s m) a -> ControllerT s m a #

Monad m => MonadState s (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

get :: ControllerT s m s #

put :: s -> ControllerT s m () #

state :: (s -> (a, s)) -> ControllerT s m a #

Monad m => MonadReader Request (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

ask :: ControllerT s m Request #

local :: (Request -> Request) -> ControllerT s m a -> ControllerT s m a #

reader :: (Request -> a) -> ControllerT s m a #

MonadTrans (ControllerT s) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

lift :: Monad m => m a -> ControllerT s m a #

Monad m => Monad (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

(>>=) :: ControllerT s m a -> (a -> ControllerT s m b) -> ControllerT s m b #

(>>) :: ControllerT s m a -> ControllerT s m b -> ControllerT s m b #

return :: a -> ControllerT s m a #

fail :: String -> ControllerT s m a #

Functor m => Functor (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

fmap :: (a -> b) -> ControllerT s m a -> ControllerT s m b #

(<$) :: a -> ControllerT s m b -> ControllerT s m a #

(Monad m, Functor m) => Applicative (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

pure :: a -> ControllerT s m a #

(<*>) :: ControllerT s m (a -> b) -> ControllerT s m a -> ControllerT s m b #

liftA2 :: (a -> b -> c) -> ControllerT s m a -> ControllerT s m b -> ControllerT s m c #

(*>) :: ControllerT s m a -> ControllerT s m b -> ControllerT s m b #

(<*) :: ControllerT s m a -> ControllerT s m b -> ControllerT s m a #

(Functor m, Monad m) => Alternative (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

empty :: ControllerT s m a #

(<|>) :: ControllerT s m a -> ControllerT s m a -> ControllerT s m a #

some :: ControllerT s m a -> ControllerT s m [a] #

many :: ControllerT s m a -> ControllerT s m [a] #

Monad m => MonadPlus (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

mzero :: ControllerT s m a #

mplus :: ControllerT s m a -> ControllerT s m a -> ControllerT s m a #

MonadIO m => MonadIO (ControllerT s m) Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Methods

liftIO :: IO a -> ControllerT s m a #

type StM (ControllerT s m) a Source # 
Instance details

Defined in Web.Simple.Controller.Trans

type StM (ControllerT s m) a = (Either Response a, s)

request :: Monad m => ControllerT s m Request Source #

Extract the request

localRequest :: Monad m => (Request -> Request) -> ControllerT s m a -> ControllerT s m a Source #

Modify the request for the given computation

controllerState :: Monad m => ControllerT s m s Source #

Extract the application-specific state

putState :: Monad m => s -> ControllerT s m () Source #

controllerApp :: Monad m => s -> ControllerT s m a -> SimpleApplication m Source #

Convert the controller into an Application

respond :: 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 :: 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 #

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 :: Monad m => StdMethod -> ControllerT s m a -> ControllerT s m () Source #

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

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.

queryParam Source #

Arguments

:: (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' :: (Monad m, Parseable a) => ByteString -> ControllerT s m a Source #

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

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 # 
Instance details

Defined in Web.Simple.Controller.Trans

Parseable Text Source # 
Instance details

Defined in Web.Simple.Controller.Trans

Parseable String Source # 
Instance details

Defined in Web.Simple.Controller.Trans

readQueryParam Source #

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.

readQueryParam' Source #

Arguments

:: (Monad m, Read a) 
=> ByteString

Parameter name

-> ControllerT s m a 

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

readQueryParams Source #

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.

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., /).

redirectBackOr Source #

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 Response Source #

Like Application, but with m as the underlying monad

type SimpleMiddleware m = SimpleApplication m -> SimpleApplication m Source #

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 #

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?"