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

Safe HaskellNone

Yesod.Core.Handler

Contents

Synopsis

Handler monad

data HandlerT site m a Source

A generic handler monad, which can have a different subsite and master site. We define a newtype for better error message.

Instances

MonadBaseControl b m => MonadBaseControl b (HandlerT site m)

Note: although we provide a MonadBaseControl instance, lifted-base's fork function is incompatible with the underlying ResourceT system. Instead, if you must fork a separate thread, you should use resourceForkIO.

Using fork usually leads to an exception that says "Control.Monad.Trans.Resource.register': The mutable state is being accessed after cleanup. Please contact the maintainers."

MonadBase b m => MonadBase b (HandlerT site m) 
MonadTrans (HandlerT site) 
Monad m => Monad (HandlerT site m) 
Monad m => Functor (HandlerT site m) 
Monad m => Applicative (HandlerT site m) 
MonadThrow m => MonadThrow (HandlerT site m) 
(MonadIO m, MonadUnsafeIO m, MonadThrow m) => MonadResource (HandlerT site m) 
MonadIO m => MonadLogger (HandlerT site m) 
MonadIO m => MonadIO (HandlerT site m) 
MonadResourceBase m => MonadHandler (HandlerT site m) 

Read information from handler

getYesod :: MonadHandler m => m (HandlerSite m)Source

Get the master site appliation argument.

getUrlRender :: MonadHandler m => m (Route (HandlerSite m) -> Text)Source

Get the URL rendering function.

getUrlRenderParams :: MonadHandler m => m (Route (HandlerSite m) -> [(Text, Text)] -> Text)Source

The URL rendering function with query-string parameters.

getCurrentRoute :: MonadHandler m => m (Maybe (Route (HandlerSite m)))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.

waiRequest :: MonadHandler m => m RequestSource

Get the request's Request value.

rawRequestBody :: MonadHandler m => Source m ByteStringSource

Stream in the raw request body without any parsing.

Since 1.2.0

Request information

Request datatype

type RequestBodyContents = ([(Text, Text)], [(Text, FileInfo)])Source

A tuple containing both the POST parameters and submitted files.

data YesodRequest Source

The parsed request information. This type augments the standard WAI Request with additional information.

Constructors

YesodRequest 

Fields

reqGetParams :: ![(Text, Text)]

Same as queryString, but decoded to Text.

reqCookies :: ![(Text, Text)]
 
reqWaiRequest :: !Request
 
reqLangs :: ![Text]

Languages which the client supports. This is an ordered list by preference.

reqToken :: !(Maybe Text)

A random, session-specific token used to prevent CSRF attacks.

reqSession :: !SessionMap

Initial session sent from the client.

Since 1.2.0

reqAccept :: ![ContentType]

An ordered list of the accepted content types.

Since 1.2.0

fileSource :: MonadResource m => FileInfo -> Source m ByteStringSource

Stream the data from the file. Since Yesod 1.2, this has been generalized to work in any MonadResource.

Convenience functions

languages :: MonadHandler m => m [Text]Source

Get the list of supported languages supplied by the user.

Languages are determined based on the following three (in descending order of preference):

  • The _LANG get parameter.
  • The _LANG cookie.
  • The _LANG user session variable.
  • Accept-Language HTTP header.

Yesod will seek the first language from the returned list matched with languages supporting by your application. This language will be used to render i18n templates. If a matching language is not found the default language will be used.

This is handled by parseWaiRequest (not exposed).

Lookup parameters

lookupGetParam :: MonadHandler m => Text -> m (Maybe Text)Source

Lookup for GET parameters.

lookupCookie :: MonadHandler m => Text -> m (Maybe Text)Source

Lookup for cookie data.

lookupFile :: (MonadHandler m, MonadResource m) => Text -> m (Maybe FileInfo)Source

Lookup for POSTed files.

lookupHeader :: MonadHandler m => CI ByteString -> m (Maybe ByteString)Source

Lookup a request header.

Since 1.2.2

Multi-lookup

lookupGetParams :: MonadHandler m => Text -> m [Text]Source

Lookup for GET parameters.

lookupPostParams :: (MonadResource m, MonadHandler m) => Text -> m [Text]Source

Lookup for POST parameters.

lookupCookies :: MonadHandler m => Text -> m [Text]Source

Lookup for cookie data.

lookupFiles :: (MonadHandler m, MonadResource m) => Text -> m [FileInfo]Source

Lookup for POSTed files.

lookupHeaders :: MonadHandler m => CI ByteString -> m [ByteString]Source

Lookup a request header.

Since 1.2.2

Responses

Pure

respond :: (Monad m, ToContent a) => ContentType -> a -> m TypedContentSource

Provide a pure value for the response body.

 respond ct = return . TypedContent ct . toContent

Since 1.2.0

Streaming

respondSource :: ContentType -> Source (HandlerT site IO) (Flush Builder) -> HandlerT site IO TypedContentSource

Use a Source for the response body.

Note that, for ease of use, the underlying monad is a HandlerT. This implies that you can run any HandlerT action. However, since a streaming response occurs after the response headers have already been sent, some actions make no sense here. For example: short-circuit responses, setting headers, changing status codes, etc.

Since 1.2.0

sendChunk :: Monad m => ToFlushBuilder a => a -> Producer m (Flush Builder)Source

In a streaming response, send a single chunk of data. This function works on most datatypes, such as ByteString and Html.

Since 1.2.0

sendFlush :: Monad m => Producer m (Flush Builder)Source

In a streaming response, send a flush command, causing all buffered data to be immediately sent to the client.

Since 1.2.0

sendChunkBS :: Monad m => ByteString -> Producer m (Flush Builder)Source

Type-specialized version of sendChunk for strict ByteStrings.

Since 1.2.0

sendChunkLBS :: Monad m => ByteString -> Producer m (Flush Builder)Source

Type-specialized version of sendChunk for lazy ByteStrings.

Since 1.2.0

sendChunkText :: Monad m => Text -> Producer m (Flush Builder)Source

Type-specialized version of sendChunk for strict Texts.

Since 1.2.0

sendChunkLazyText :: Monad m => Text -> Producer m (Flush Builder)Source

Type-specialized version of sendChunk for lazy Texts.

Since 1.2.0

sendChunkHtml :: Monad m => Html -> Producer m (Flush Builder)Source

Type-specialized version of sendChunk for Htmls.

Since 1.2.0

Redirecting

class RedirectUrl master a whereSource

Some value which can be turned into a URL for redirects.

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => a -> m TextSource

Converts the value to the URL and a list of query-string parameters.

Instances

RedirectUrl master String 
RedirectUrl master Text 
RedirectUrl master (Route master) 
(RedirectUrl master a, PathPiece b) => RedirectUrl master (Fragment a b) 
(~ * key Text, ~ * val Text) => RedirectUrl master (Route master, Map key val) 
(~ * key Text, ~ * val Text) => RedirectUrl master (Route master, [(key, val)]) 

redirect :: (MonadHandler m, RedirectUrl (HandlerSite m) url) => url -> m aSource

Redirect to the given route. HTTP status code 303 for HTTP 1.1 clients and 302 for HTTP 1.0 This is the appropriate choice for a get-following-post technique, which should be the usual use case.

If you want direct control of the final status code, or need a different status code, please use redirectWith.

redirectWith :: (MonadHandler m, RedirectUrl (HandlerSite m) url) => Status -> url -> m aSource

Redirect to the given URL with the specified status code.

redirectToPost :: (MonadHandler m, RedirectUrl (HandlerSite m) url) => url -> m aSource

Redirect to a POST resource.

This is not technically a redirect; instead, it returns an HTML page with a POST form, and some Javascript to automatically submit the form. This can be useful when you need to post a plain link somewhere that needs to cause changes on the server.

data Fragment a b Source

Add a fragment identifier to a route to be used when redirecting. For example:

 redirect (NewsfeedR :#: storyId)

Since 1.2.9.

Constructors

a :#: b 

Instances

Typeable2 Fragment 
(RedirectUrl master a, PathPiece b) => RedirectUrl master (Fragment a b) 
(Show a, Show b) => Show (Fragment a b) 

Errors

notFound :: MonadHandler m => m aSource

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

badMethod :: MonadHandler m => m aSource

Return a 405 method not supported page.

notAuthenticated :: MonadHandler m => m aSource

Return a 401 status code

permissionDenied :: MonadHandler m => Text -> m aSource

Return a 403 permission denied page.

permissionDeniedI :: (RenderMessage (HandlerSite m) msg, MonadHandler m) => msg -> m aSource

Return a 403 permission denied page.

invalidArgs :: MonadHandler m => [Text] -> m aSource

Return a 400 invalid arguments page.

invalidArgsI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => [msg] -> m aSource

Return a 400 invalid arguments page.

Short-circuit responses.

sendFile :: MonadHandler m => ContentType -> FilePath -> m 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.

sendFilePartSource

Arguments

:: MonadHandler m 
=> ContentType 
-> FilePath 
-> Integer

offset

-> Integer

count

-> m a 

Same as sendFile, but only sends part of a file.

sendResponse :: (MonadHandler m, ToTypedContent c) => c -> m aSource

Bypass remaining handler code and output the given content with a 200 status code.

sendResponseStatus :: (MonadHandler m, ToTypedContent c) => Status -> c -> m aSource

Bypass remaining handler code and output the given content with the given status code.

sendResponseCreated :: MonadHandler m => Route (HandlerSite m) -> m aSource

Send a 201 Created response with the given route as the Location response header.

sendWaiResponse :: MonadHandler m => Response -> m bSource

Send a Response. Please note: this function is rarely necessary, and will disregard any changes to response headers and session that you have already specified. This function short-circuits. It should be considered only for very specific needs. If you are not sure if you need it, you don't.

sendRawResponse :: (MonadHandler m, MonadBaseControl IO m) => (Source IO ByteString -> Sink ByteString IO () -> m ()) -> m aSource

Send a raw response. This is used for cases such as WebSockets. Requires WAI 2.1 or later, and a web server which supports raw responses (e.g., Warp).

Since 1.2.7

Different representations

HTTP allows content negotation to determine what representation of data you would like to use. The most common example of this is providing both a user-facing HTML page and an API facing JSON response from the same URL. The means of achieving this is the Accept HTTP header, which provides a list of content types the client will accept, sorted by preference.

By using selectRep and provideRep, you can provide a number of different representations, e.g.:

 selectRep $ do
   provideRep typeHtml $ produceHtmlOutput
   provideRep typeJson $ produceJsonOutput

The first provided representation will be used if no matches are found.

selectRep :: MonadHandler m => Writer (Endo [ProvidedRep m]) () -> m TypedContentSource

Select a representation to send to the client based on the representations provided inside this do-block. Should be used together with provideRep.

Since 1.2.0

provideRep :: (Monad m, HasContentType a) => m a -> Writer (Endo [ProvidedRep m]) ()Source

Provide a single representation to be used, based on the request of the client. Should be used together with selectRep.

Since 1.2.0

provideRepType :: (Monad m, ToContent a) => ContentType -> m a -> Writer (Endo [ProvidedRep m]) ()Source

Same as provideRep, but instead of determining the content type from the type of the value itself, you provide the content type separately. This can be a convenience instead of creating newtype wrappers for uncommonly used content types.

 provideRepType "application/x-special-format" "This is the content"

Since 1.2.0

data ProvidedRep m Source

Internal representation of a single provided representation.

Since 1.2.0

Setting headers

setCookie :: MonadHandler m => SetCookie -> m ()Source

Set the cookie on the client.

getExpiresSource

Arguments

:: MonadIO m 
=> Int

minutes

-> m UTCTime 

Helper function for setCookieExpires value

deleteCookieSource

Arguments

:: MonadHandler m 
=> Text

key

-> Text

path

-> m () 

Unset the cookie on the client.

Note: although the value used for key and path is Text, you should only use ASCII values to be HTTP compliant.

addHeader :: MonadHandler m => Text -> Text -> m ()Source

Set an arbitrary response header.

Note that, while the data type used here is Text, you must provide only ASCII value to be HTTP compliant.

Since 1.2.0

setHeader :: MonadHandler m => Text -> Text -> m ()Source

Deprecated: Please use addHeader instead

Deprecated synonym for addHeader.

setLanguage :: MonadHandler m => Text -> m ()Source

Set the language in the user session. Will show up in languages on the next request.

Content caching and expiration

cacheSeconds :: MonadHandler m => Int -> m ()Source

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

neverExpires :: MonadHandler m => m ()Source

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

alreadyExpired :: MonadHandler m => m ()Source

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

expiresAt :: MonadHandler m => UTCTime -> m ()Source

Set an Expires header to the given date.

Session

lookupSession :: MonadHandler m => Text -> m (Maybe Text)Source

Lookup for session data.

lookupSessionBS :: MonadHandler m => Text -> m (Maybe ByteString)Source

Lookup for session data in binary format.

getSession :: MonadHandler m => m SessionMapSource

Get all session variables.

setSessionSource

Arguments

:: MonadHandler m 
=> Text

key

-> Text

value

-> m () 

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.

setSessionBS :: MonadHandler m => Text -> ByteString -> m ()Source

Same as setSession, but uses binary data for the value.

deleteSession :: MonadHandler m => Text -> m ()Source

Unsets a session variable. See setSession.

clearSession :: MonadHandler m => m ()Source

Clear all session variables.

Since: 1.0.1

Ultimate destination

setUltDest :: (MonadHandler m, RedirectUrl (HandlerSite m) url) => url -> m ()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.

setUltDestCurrent :: MonadHandler m => m ()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.

setUltDestReferer :: MonadHandler m => m ()Source

Sets the ultimate destination to the referer request header, if present.

This function will not overwrite an existing ultdest.

redirectUltDestSource

Arguments

:: (RedirectUrl (HandlerSite m) url, MonadHandler m) 
=> url

default destination if nothing in session

-> m a 

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

The ultimate destination is set with setUltDest.

This function uses redirect, and thus will perform a temporary redirect to a GET request.

clearUltDest :: MonadHandler m => m ()Source

Remove a previously set ultimate destination. See setUltDest.

Messages

setMessage :: MonadHandler m => Html -> m ()Source

Sets a message in the user's session.

See getMessage.

setMessageI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => msg -> m ()Source

Sets a message in the user's session.

See getMessage.

getMessage :: MonadHandler m => m (Maybe Html)Source

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

See setMessage.

Helpers for specific content

Hamlet

hamletToRepHtml :: MonadHandler m => HtmlUrl (Route (HandlerSite m)) -> m HtmlSource

Deprecated: Use giveUrlRenderer instead

Wraps the Content generated by hamletToContent in a RepHtml.

giveUrlRenderer :: MonadHandler m => ((Route (HandlerSite m) -> [(Text, Text)] -> Text) -> output) -> m outputSource

Provide a URL rendering function to the given function and return the result. Useful for processing Shakespearean templates.

Since 1.2.0

Misc

newIdent :: MonadHandler m => m TextSource

Get a unique identifier.

Lifting

handlerToIO :: (MonadIO m1, MonadIO m2) => HandlerT site m1 (HandlerT site IO a -> m2 a)Source

Returns a function that runs HandlerT actions inside IO.

Sometimes you want to run an inner HandlerT action outside the control flow of an HTTP request (on the outer HandlerT action). For example, you may want to spawn a new thread:

 getFooR :: Handler RepHtml
 getFooR = do
   runInnerHandler <- handlerToIO
   liftIO $ forkIO $ runInnerHandler $ do
     Code here runs inside GHandler but on a new thread.
     This is the inner GHandler.
     ...
   Code here runs inside the request's control flow.
   This is the outer GHandler.
   ...

Another use case for this function is creating a stream of server-sent events using GHandler actions (see yesod-eventsource).

Most of the environment from the outer GHandler is preserved on the inner GHandler, however:

  • The request body is cleared (otherwise it would be very difficult to prevent huge memory leaks).
  • The cache is cleared (see CacheKey).

Changes to the response made inside the inner GHandler are ignored (e.g., session variables, cookies, response headers). This allows the inner GHandler to outlive the outer GHandler (e.g., on the forkIO example above, a response may be sent to the client without killing the new thread).

forkHandlerSource

Arguments

:: (SomeException -> HandlerT site IO ())

error handler

-> HandlerT site IO () 
-> HandlerT site IO () 

forkIO for a Handler (run an action in the background)

Uses handlerToIO, liftResourceT, and resourceForkIO for correctness and efficiency

Since 1.2.8

i18n

getMessageRender :: (MonadHandler m, RenderMessage (HandlerSite m) message) => m (message -> Text)Source

Per-request caching

cached :: (MonadHandler m, Typeable a) => m a -> m aSource

Use a per-request cache to avoid performing the same action multiple times. Note that values are stored by their type. Therefore, you should use newtype wrappers to distinguish logically different types.

Since 1.2.0