yesod-0.5.4.2: Creation of type-safe, RESTful web applications.

Yesod.Handler

Contents

Synopsis

Type families

type family Route a Source

The type-safe URLs associated with a site argument.

Handler monad

data GHandler sub master a Source

A generic handler monad, which can have a different subsite and master site. This monad is a combination of ReaderT for basic arguments, a WriterT for headers and session, and an MEitherT monad for handling special responses. It is declared as a newtype to make compiler errors more readable.

Instances

Failure ErrorResponse (GHandler sub master) 
Monad (GHandler sub master) 
Functor (GHandler sub master) 
Applicative (GHandler sub master) 
MonadCatchIO (GHandler sub master) 
MonadIO (GHandler sub master) 
RequestReader (GHandler sub master) 

Read information from handler

getYesod :: GHandler sub master masterSource

Get the master site appliation argument.

getYesodSub :: GHandler sub master subSource

Get the sub application argument.

getUrlRender :: GHandler sub master (Route master -> String)Source

Get the URL rendering function.

getUrlRenderParams :: GHandler sub master (Route master -> [(String, String)] -> String)Source

The URL rendering function with query-string parameters.

getCurrentRoute :: GHandler sub master (Maybe (Route sub))Source

Get the route requested by the user. If this is a 404 response- where the user requested an invalid route- this function will return Nothing.

getRouteToMaster :: GHandler sub master (Route sub -> Route master)Source

Get the function to promote a route for a subsite to a route for the master site.

Special responses

Redirecting

data RedirectType Source

Different types of redirects.

redirect :: RedirectType -> Route master -> GHandler sub master aSource

Redirect to the given route.

redirectParams :: RedirectType -> Route master -> [(String, String)] -> GHandler sub master aSource

Redirects to the given route with the associated query-string parameters.

redirectString :: RedirectType -> String -> GHandler sub master aSource

Redirect to the given URL.

Errors

notFound :: Failure ErrorResponse m => m aSource

Return a 404 not found page. Also denotes no handler available.

badMethod :: (RequestReader m, Failure ErrorResponse m) => m aSource

Return a 405 method not supported page.

permissionDenied :: Failure ErrorResponse m => String -> m aSource

Return a 403 permission denied page.

invalidArgs :: Failure ErrorResponse m => [String] -> m aSource

Return a 400 invalid arguments page.

Short-circuit responses.

sendFile :: ContentType -> FilePath -> GHandler sub master aSource

Bypass remaining handler code and output the given file.

For some backends, this is more efficient than reading in the file to memory, since they can optimize file sending via a system call to sendfile.

sendResponse :: HasReps c => c -> GHandler sub master aSource

Bypass remaining handler code and output the given content.

Setting headers

setCookieSource

Arguments

:: Int

minutes to timeout

-> String

key

-> String

value

-> GHandler sub master () 

Set the cookie on the client.

deleteCookie :: String -> GHandler sub master ()Source

Unset the cookie on the client.

setHeader :: String -> String -> GHandler sub master ()Source

Set an arbitrary response header.

setLanguage :: String -> GHandler sub master ()Source

Set the language in the user session. Will show up in languages.

Content caching and expiration

cacheSeconds :: Int -> GHandler s m ()Source

Set the Cache-Control header to indicate this response should be cached for the given number of seconds.

neverExpires :: GHandler s m ()Source

Set the Expires header to some date in 2037. In other words, this content is never (realistically) expired.

alreadyExpired :: GHandler s m ()Source

Set an Expires header in the past, meaning this content should not be cached.

expiresAt :: UTCTime -> GHandler s m ()Source

Set an Expires header to the given date.

Session

setSessionSource

Arguments

:: String

key

-> String

value

-> GHandler sub master () 

Set a variable in the user's session.

The session is handled by the clientsession package: it sets an encrypted and hashed cookie on the client. This ensures that all data is secure and not tampered with.

deleteSession :: String -> GHandler sub master ()Source

Unsets a session variable. See setSession.

Ultimate destination

setUltDest :: Route master -> GHandler sub master ()Source

Sets the ultimate destination variable to the given route.

An ultimate destination is stored in the user session and can be loaded later by redirectUltDest.

setUltDestString :: String -> GHandler sub master ()Source

Same as setUltDest, but use the given string.

setUltDest' :: GHandler sub master ()Source

Same as setUltDest, but uses the current page.

If this is a 404 handler, there is no current page, and then this call does nothing.

redirectUltDestSource

Arguments

:: RedirectType 
-> Route master

default destination if nothing in session

-> GHandler sub master () 

Redirect to the ultimate destination in the user's session. Clear the value from the session.

The ultimate destination is set with setUltDest.

Messages

setMessage :: Html -> GHandler sub master ()Source

Sets a message in the user's session.

The message set here will not be visible within the current request; instead, it will only appear in the next request.

See getMessage.

getMessage :: GHandler sub master (Maybe Html)Source

Gets the message in the user's session, if available, and then clears the variable.

See setMessage.

Internal Yesod

runHandler :: HasReps c => GHandler sub master c -> (Route master -> [(String, String)] -> String) -> Maybe (Route sub) -> (Route sub -> Route master) -> master -> (master -> sub) -> YesodAppSource

Function used internally by Yesod in the process of converting a GHandler into an Application. Should not be needed by users.

newtype YesodApp Source

An extension of the basic WAI Application datatype to provide extra features needed by Yesod. Users should never need to use this directly, as the GHandler monad and template haskell code should hide it away.

toMasterHandler :: (Route sub -> Route master) -> (master -> sub) -> Route sub -> GHandler sub master a -> GHandler master master aSource

Used internally for promoting subsite handler functions to master site handler functions. Should not be needed by users.

finallyHandler :: GHandler s m a -> GHandler s m b -> GHandler s m aSource

A version of finally which works correctly with short-circuiting.