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

Safe HaskellNone
LanguageHaskell98

Yesod.Core.Handler

Contents

Synopsis

Handler monad

type HandlerT site (m :: * -> *) = HandlerFor site Source #

Deprecated: Use HandlerFor directly

data HandlerFor site a Source #

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

Instances
Monad (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

(>>=) :: HandlerFor site a -> (a -> HandlerFor site b) -> HandlerFor site b #

(>>) :: HandlerFor site a -> HandlerFor site b -> HandlerFor site b #

return :: a -> HandlerFor site a #

fail :: String -> HandlerFor site a #

Functor (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

fmap :: (a -> b) -> HandlerFor site a -> HandlerFor site b #

(<$) :: a -> HandlerFor site b -> HandlerFor site a #

Applicative (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

pure :: a -> HandlerFor site a #

(<*>) :: HandlerFor site (a -> b) -> HandlerFor site a -> HandlerFor site b #

liftA2 :: (a -> b -> c) -> HandlerFor site a -> HandlerFor site b -> HandlerFor site c #

(*>) :: HandlerFor site a -> HandlerFor site b -> HandlerFor site b #

(<*) :: HandlerFor site a -> HandlerFor site b -> HandlerFor site a #

MonadIO (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

liftIO :: IO a -> HandlerFor site a #

MonadUnliftIO (HandlerFor site) Source #

Since: 1.4.38

Instance details

Defined in Yesod.Core.Types

Methods

askUnliftIO :: HandlerFor site (UnliftIO (HandlerFor site)) #

withRunInIO :: ((forall a. HandlerFor site a -> IO a) -> IO b) -> HandlerFor site b #

MonadResource (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

liftResourceT :: ResourceT IO a -> HandlerFor site a #

PrimMonad (HandlerFor site) Source #

Since: 1.6.7

Instance details

Defined in Yesod.Core.Types

Associated Types

type PrimState (HandlerFor site) :: Type #

Methods

primitive :: (State# (PrimState (HandlerFor site)) -> (#State# (PrimState (HandlerFor site)), a#)) -> HandlerFor site a #

MonadThrow (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

throwM :: Exception e => e -> HandlerFor site a #

MonadLogger (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> HandlerFor site () #

MonadLoggerIO (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

askLoggerIO :: HandlerFor site (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

MonadHandler (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Class.Handler

Associated Types

type HandlerSite (HandlerFor site) :: Type Source #

type SubHandlerSite (HandlerFor site) :: Type Source #

MonadReader (HandlerData site site) (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

ask :: HandlerFor site (HandlerData site site) #

local :: (HandlerData site site -> HandlerData site site) -> HandlerFor site a -> HandlerFor site a #

reader :: (HandlerData site site -> a) -> HandlerFor site a #

type PrimState (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Types

type HandlerSite (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Class.Handler

type HandlerSite (HandlerFor site) = site
type SubHandlerSite (HandlerFor site) Source # 
Instance details

Defined in Yesod.Core.Class.Handler

type SubHandlerSite (HandlerFor site) = site

Read information from handler

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

Get the master site application argument.

getsYesod :: MonadHandler m => (HandlerSite m -> a) -> m a Source #

Get a specific component of the master site application argument. Analogous to the gets function for operating on StateT.

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.

getPostParams :: MonadHandler m => m [(Text, Text)] Source #

Get all the post parameters passed to the handler. To also get the submitted files (if any), you have to use runRequestBody instead of this function.

Since: 1.4.33

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

Get the request's Request value.

rawRequestBody :: MonadHandler m => ConduitT i ByteString m () Source #

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

fileSource :: MonadResource m => FileInfo -> ConduitT () ByteString m () Source #

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

fileSourceByteString :: MonadResource m => FileInfo -> m ByteString Source #

Extract a strict ByteString body from a FileInfo.

This function will block while reading the file.

do
    fileByteString <- fileSourceByteString fileInfo

Since: 1.6.5

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 (in descending order of preference):

  • The _LANG user session variable.
  • The _LANG get parameter.
  • The _LANG cookie.
  • 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 => 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

Lookup authentication data

lookupBasicAuth :: MonadHandler m => m (Maybe (Text, Text)) Source #

Lookup basic authentication data from Authorization header of request. Returns user name and password

Since: 1.4.9

lookupBearerAuth :: MonadHandler m => m (Maybe Text) Source #

Lookup bearer authentication datafrom Authorization header of request. Returns bearer token value

Since: 1.4.9

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 => 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 TypedContent Source #

Provide a pure value for the response body.

respond ct = return . TypedContent ct . toContent

Since: 1.2.0

Streaming

respondSource :: ContentType -> ConduitT () (Flush Builder) (HandlerFor site) () -> HandlerFor site TypedContent Source #

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 -> ConduitT i (Flush Builder) m () 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 => ConduitT i (Flush Builder) m () 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 -> ConduitT i (Flush Builder) m () Source #

Type-specialized version of sendChunk for strict ByteStrings.

Since: 1.2.0

sendChunkLBS :: Monad m => ByteString -> ConduitT i (Flush Builder) m () Source #

Type-specialized version of sendChunk for lazy ByteStrings.

Since: 1.2.0

sendChunkText :: Monad m => Text -> ConduitT i (Flush Builder) m () Source #

Type-specialized version of sendChunk for strict Texts.

Since: 1.2.0

sendChunkLazyText :: Monad m => Text -> ConduitT i (Flush Builder) m () Source #

Type-specialized version of sendChunk for lazy Texts.

Since: 1.2.0

sendChunkHtml :: Monad m => Html -> ConduitT i (Flush Builder) m () Source #

Type-specialized version of sendChunk for Htmls.

Since: 1.2.0

Redirecting

class RedirectUrl master a where Source #

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

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => a -> m Text Source #

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

Instances
RedirectUrl master String Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => String -> m Text Source #

RedirectUrl master Text Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => Text -> m Text Source #

RedirectUrl master (Route master) Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => Route master -> m Text Source #

(RedirectUrl master a, PathPiece b) => RedirectUrl master (Fragment a b) Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => Fragment a b -> m Text Source #

(key ~ Text, val ~ Text) => RedirectUrl master (Route master, Map key val) Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => (Route master, Map key val) -> m Text Source #

(key ~ Text, val ~ Text) => RedirectUrl master (Route master, [(key, val)]) Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => (Route master, [(key, val)]) -> m Text Source #

redirect :: (MonadHandler m, RedirectUrl (HandlerSite m) url) => url -> m a Source #

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

Redirect to the given URL with the specified status code.

redirectToPost :: (MonadHandler m, RedirectUrl (HandlerSite m) url) => url -> m a Source #

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
(RedirectUrl master a, PathPiece b) => RedirectUrl master (Fragment a b) Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => Fragment a b -> m Text Source #

(Show a, Show b) => Show (Fragment a b) Source # 
Instance details

Defined in Yesod.Core.Handler

Methods

showsPrec :: Int -> Fragment a b -> ShowS #

show :: Fragment a b -> String #

showList :: [Fragment a b] -> ShowS #

Errors

notFound :: MonadHandler m => m a Source #

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

badMethod :: MonadHandler m => m a Source #

Return a 405 method not supported page.

notAuthenticated :: MonadHandler m => m a Source #

Return a 401 status code

permissionDenied :: MonadHandler m => Text -> m a Source #

Return a 403 permission denied page.

permissionDeniedI :: (RenderMessage (HandlerSite m) msg, MonadHandler m) => msg -> m a Source #

Return a 403 permission denied page.

invalidArgs :: MonadHandler m => [Text] -> m a Source #

Return a 400 invalid arguments page.

invalidArgsI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => [msg] -> m a Source #

Return a 400 invalid arguments page.

Short-circuit responses

Note that since short-circuiting is implemented by using exceptions, using e.g. sendStatusJSON inside a runDB block will result in the database actions getting rolled back:

runDB $ do
  userId <- insert $ User "username" "email@example.com"
  postId <- insert $ BlogPost "title" "hi there!"
    The previous two inserts will be rolled back.
  sendStatusJSON Status.status200 ()

sendFile :: MonadHandler m => ContentType -> FilePath -> m a Source #

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.

sendFilePart Source #

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

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

sendResponseStatus :: (MonadHandler m, ToTypedContent c) => Status -> c -> m a Source #

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

Type specific response with custom status

sendStatusJSON :: (MonadHandler m, ToJSON c) => Status -> c -> m a Source #

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

Since: 1.4.18

sendResponseCreated :: MonadHandler m => Route (HandlerSite m) -> m a Source #

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

sendResponseNoContent :: MonadHandler m => m a Source #

Bypass remaining handler code and output no content with a 204 status code.

Since: 1.6.9

sendWaiResponse :: MonadHandler m => Response -> m b Source #

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.

sendWaiApplication :: MonadHandler m => Application -> m b Source #

Switch over to handling the current request with a WAI Application.

Since: 1.2.17

sendRawResponse :: (MonadHandler m, MonadUnliftIO m) => (ConduitT () ByteString IO () -> ConduitT ByteString Void IO () -> m ()) -> m a Source #

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

sendRawResponseNoConduit :: (MonadHandler m, MonadUnliftIO m) => (IO ByteString -> (ByteString -> IO ()) -> m ()) -> m a Source #

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

Since: 1.2.16

notModified :: MonadHandler m => m a Source #

Send a 304 not modified response immediately. This is a short-circuiting action.

Since: 1.4.4

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 produceHtmlOutput
  provideRep produceJsonOutput

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

selectRep :: MonadHandler m => Writer (Endo [ProvidedRep m]) () -> m TypedContent Source #

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.

getExpires Source #

Arguments

:: MonadIO m 
=> Int

minutes

-> m UTCTime 

Helper function for setCookieExpires value

deleteCookie Source #

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.

replaceOrAddHeader :: MonadHandler m => Text -> Text -> m () Source #

Replace an existing header with a new value or add a new header if not present.

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

Since: 1.4.36

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

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

addContentDispositionFileName :: MonadHandler m => Text -> m () Source #

Set attachment file name.

Allows Unicode characters by encoding to UTF-8. Some modurn browser parse UTF-8 characters with out encoding setting. But, for example IE9 can't parse UTF-8 characters. This function use RFC 6266(RFC 5987)

Since: 1.6.4

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.

setEtag :: MonadHandler m => Text -> m () Source #

Check the if-none-match header and, if it matches the given value, return a 304 not modified response. Otherwise, set the etag header to the given value.

Note that it is the responsibility of the caller to ensure that the provided value is a valid etag value, no sanity checking is performed by this function.

Since: 1.4.4

setWeakEtag :: MonadHandler m => Text -> m () Source #

Check the if-none-match header and, if it matches the given value, return a 304 not modified response. Otherwise, set the etag header to the given value.

A weak etag is only expected to be semantically identical to the prior content, but doesn't have to be byte-for-byte identical. Therefore it can be useful for dynamically generated content that may be difficult to perform bytewise hashing upon.

Note that it is the responsibility of the caller to ensure that the provided value is a valid etag value, no sanity checking is performed by this function.

Since: 1.4.37

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

Get all session variables.

setSession Source #

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.

redirectUltDest Source #

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

addMessage Source #

Arguments

:: MonadHandler m 
=> Text

status

-> Html

message

-> m () 

Adds a status and message in the user's session.

See getMessages.

Since: 1.4.20

addMessageI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => Text -> msg -> m () Source #

Adds a message in the user's session but uses RenderMessage to allow for i18n

See getMessages.

Since: 1.4.20

getMessages :: MonadHandler m => m [(Text, Html)] Source #

Gets all messages in the user's session, and then clears the variable.

See addMessage.

Since: 1.4.20

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

Calls addMessage with an empty status

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

Calls addMessageI with an empty status

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

Gets just the last message in the user's session, discards the rest and the status

Subsites

data SubHandlerFor sub master a Source #

A handler monad for subsite

Since: 1.6.0

Instances
Monad (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

(>>=) :: SubHandlerFor child master a -> (a -> SubHandlerFor child master b) -> SubHandlerFor child master b #

(>>) :: SubHandlerFor child master a -> SubHandlerFor child master b -> SubHandlerFor child master b #

return :: a -> SubHandlerFor child master a #

fail :: String -> SubHandlerFor child master a #

Functor (SubHandlerFor sub master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

fmap :: (a -> b) -> SubHandlerFor sub master a -> SubHandlerFor sub master b #

(<$) :: a -> SubHandlerFor sub master b -> SubHandlerFor sub master a #

Applicative (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

pure :: a -> SubHandlerFor child master a #

(<*>) :: SubHandlerFor child master (a -> b) -> SubHandlerFor child master a -> SubHandlerFor child master b #

liftA2 :: (a -> b -> c) -> SubHandlerFor child master a -> SubHandlerFor child master b -> SubHandlerFor child master c #

(*>) :: SubHandlerFor child master a -> SubHandlerFor child master b -> SubHandlerFor child master b #

(<*) :: SubHandlerFor child master a -> SubHandlerFor child master b -> SubHandlerFor child master a #

MonadIO (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

liftIO :: IO a -> SubHandlerFor child master a #

MonadUnliftIO (SubHandlerFor child master) Source #

Since: 1.4.38

Instance details

Defined in Yesod.Core.Types

Methods

askUnliftIO :: SubHandlerFor child master (UnliftIO (SubHandlerFor child master)) #

withRunInIO :: ((forall a. SubHandlerFor child master a -> IO a) -> IO b) -> SubHandlerFor child master b #

MonadResource (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

liftResourceT :: ResourceT IO a -> SubHandlerFor child master a #

MonadThrow (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

throwM :: Exception e => e -> SubHandlerFor child master a #

MonadLogger (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> SubHandlerFor child master () #

MonadLoggerIO (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

askLoggerIO :: SubHandlerFor child master (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

MonadHandler (SubHandlerFor sub master) Source # 
Instance details

Defined in Yesod.Core.Class.Handler

Associated Types

type HandlerSite (SubHandlerFor sub master) :: Type Source #

type SubHandlerSite (SubHandlerFor sub master) :: Type Source #

MonadReader (HandlerData child master) (SubHandlerFor child master) Source # 
Instance details

Defined in Yesod.Core.Types

Methods

ask :: SubHandlerFor child master (HandlerData child master) #

local :: (HandlerData child master -> HandlerData child master) -> SubHandlerFor child master a -> SubHandlerFor child master a #

reader :: (HandlerData child master -> a) -> SubHandlerFor child master a #

type HandlerSite (SubHandlerFor sub master) Source # 
Instance details

Defined in Yesod.Core.Class.Handler

type HandlerSite (SubHandlerFor sub master) = master
type SubHandlerSite (SubHandlerFor sub master) Source # 
Instance details

Defined in Yesod.Core.Class.Handler

type SubHandlerSite (SubHandlerFor sub master) = sub

Helpers for specific content

Hamlet

hamletToRepHtml :: MonadHandler m => HtmlUrl (Route (HandlerSite m)) -> m Html Source #

Deprecated: Use withUrlRenderer instead

Wraps the Content generated by hamletToContent in a RepHtml.

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

Deprecated: Use withUrlRenderer instead

Deprecated synonym for withUrlRenderer.

Since: 1.2.0

withUrlRenderer :: MonadHandler m => ((Route (HandlerSite m) -> [(Text, Text)] -> Text) -> output) -> m output Source #

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

Since: 1.2.20

Misc

newIdent :: MonadHandler m => m Text Source #

Get a unique identifier.

Lifting

handlerToIO :: MonadIO m => HandlerFor site (HandlerFor site a -> m 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).

forkHandler Source #

Arguments

:: (SomeException -> HandlerFor site ())

error handler

-> HandlerFor site () 
-> HandlerFor site () 

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

Use a per-request cache to avoid performing the same action multiple times. Values are stored by their type, the result of typeOf from Typeable. Therefore, you should use different newtype wrappers at each cache site.

For example, yesod-auth uses an un-exported newtype, CachedMaybeAuth and exports functions that utilize it such as maybeAuth. This means that another module can create its own newtype wrapper to cache the same type from a different action without any cache conflicts.

See the original announcement: http://www.yesodweb.com/blog/2013/03/yesod-1-2-cleaner-internals

Since: 1.2.0

cacheGet :: (MonadHandler m, Typeable a) => m (Maybe a) Source #

Retrieves a value from the cache used by cached.

Since: 1.6.10

cacheSet :: (MonadHandler m, Typeable a) => a -> m () Source #

Sets a value in the cache used by cached.

Since: 1.6.10

cachedBy :: (MonadHandler m, Typeable a) => ByteString -> m a -> m a Source #

a per-request cache. just like cached. cached can only cache a single value per type. cachedBy stores multiple values per type by usage of a ByteString key

cached is ideal to cache an action that has only one value of a type, such as the session's current user cachedBy is required if the action has parameters and can return multiple values per type. You can turn those parameters into a ByteString cache key. For example, caching a lookup of a Link by a token where multiple token lookups might be performed.

Since: 1.4.0

cacheByGet :: (MonadHandler m, Typeable a) => ByteString -> m (Maybe a) Source #

Retrieves a value from the cache used by cachedBy.

Since: 1.6.10

cacheBySet :: (MonadHandler m, Typeable a) => ByteString -> a -> m () Source #

Sets a value in the cache used by cachedBy.

Since: 1.6.10

AJAX CSRF protection

When a user has authenticated with your site, all requests made from the browser to your server will include the session information that you use to verify that the user is logged in. Unfortunately, this allows attackers to make unwanted requests on behalf of the user by e.g. submitting an HTTP request to your site when the user visits theirs. This is known as a Cross Site Request Forgery (CSRF) attack.

To combat this attack, you need a way to verify that the request is valid. This is achieved by generating a random string ("token"), storing it in your encrypted session so that the server can look it up (see reqToken), and adding the token to HTTP requests made to your server. When a request comes in, the token in the request is compared to the one from the encrypted session. If they match, you can be sure the request is valid.

Yesod implements this behavior in two ways:

  1. The yesod-form package stores the CSRF token in a hidden field in the form, then validates it with functions like runFormPost.
  2. Yesod can store the CSRF token in a cookie which is accessible by Javascript. Requests made by Javascript can lookup this cookie and add it as a header to requests. The server then checks the token in the header against the one in the encrypted session.

The form-based approach has the advantage of working for users with Javascript disabled, while adding the token to the headers with Javascript allows things like submitting JSON or binary data in AJAX requests. Yesod supports checking for a CSRF token in either the POST parameters of the form (checkCsrfParamNamed), the headers (checkCsrfHeaderNamed), or both options (checkCsrfHeaderOrParam).

The easiest way to check both sources is to add the defaultCsrfMiddleware to your Yesod Middleware.

Opting-out of CSRF checking for specific routes

(Note: this code is generic to opting out of any Yesod middleware)

yesodMiddleware app = do
  maybeRoute <- getCurrentRoute
  let dontCheckCsrf = case maybeRoute of
                        Just HomeR                     -> True  -- Don't check HomeR
                        Nothing                        -> True  -- Don't check for 404s
                        _                              -> False -- Check other routes

  defaultYesodMiddleware $ defaultCsrfSetCookieMiddleware $ (if dontCheckCsrf then id else defaultCsrfCheckMiddleware) $ app

This can also be implemented using the csrfCheckMiddleware function.

Setting CSRF Cookies

setCsrfCookie :: MonadHandler m => m () Source #

Sets a cookie with a CSRF token, using defaultCsrfCookieName for the cookie name.

The cookie's path is set to /, making it valid for your whole website.

Since: 1.4.14

setCsrfCookieWithCookie :: MonadHandler m => SetCookie -> m () Source #

Takes a SetCookie and overrides its value with a CSRF token, then sets the cookie.

Make sure to set the setCookiePath to the root path of your application, otherwise you'll generate a new CSRF token for every path of your app. If your app is run from from e.g. www.example.com/app1, use app1. The vast majority of sites will just use /.

Since: 1.4.14

defaultCsrfCookieName :: ByteString Source #

The default cookie name for the CSRF token ("XSRF-TOKEN").

Since: 1.4.14

Looking up CSRF Headers

checkCsrfHeaderNamed :: MonadHandler m => CI ByteString -> m () Source #

Takes a header name to lookup a CSRF token. If the value doesn't match the token stored in the session, this function throws a PermissionDenied error.

Since: 1.4.14

hasValidCsrfHeaderNamed :: MonadHandler m => CI ByteString -> m Bool Source #

Takes a header name to lookup a CSRF token, and returns whether the value matches the token stored in the session.

Since: 1.4.14

defaultCsrfHeaderName :: CI ByteString Source #

The default header name for the CSRF token ("X-XSRF-TOKEN").

Since: 1.4.14

Looking up CSRF POST Parameters

hasValidCsrfParamNamed :: MonadHandler m => Text -> m Bool Source #

Takes a POST parameter name to lookup a CSRF token, and returns whether the value matches the token stored in the session.

Since: 1.4.14

checkCsrfParamNamed :: MonadHandler m => Text -> m () Source #

Takes a POST parameter name to lookup a CSRF token. If the value doesn't match the token stored in the session, this function throws a PermissionDenied error.

Since: 1.4.14

defaultCsrfParamName :: Text Source #

The default parameter name for the CSRF token ("_token")

Since: 1.4.14

Checking CSRF Headers or POST Parameters

checkCsrfHeaderOrParam Source #

Arguments

:: (MonadHandler m, MonadLogger m) 
=> CI ByteString

The header name to lookup the CSRF token

-> Text

The POST parameter name to lookup the CSRF token

-> m () 

Checks that a valid CSRF token is present in either the request headers or POST parameters. If the value doesn't match the token stored in the session, this function throws a PermissionDenied error.

Since: 1.4.14