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

Safe HaskellNone

Yesod.Handler

Contents

Synopsis

Type families

class YesodSubRoute s y whereSource

Methods

fromSubRoute :: s -> y -> Route s -> Route ySource

Handler monad

data GHandler sub master a Source

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

Instances

MonadBase IO (GHandler sub master) 
MonadBaseControl IO (GHandler sub master) 
MonadLift (ResourceT IO) (GHandler sub master) 
Monad (GHandler sub master) 
Functor (GHandler sub master) 
Applicative (GHandler sub master) 
MonadUnsafeIO (GHandler sub master) 
MonadThrow (GHandler sub master) 
MonadResource (GHandler sub master) 
MonadLogger (GHandler sub master) 
MonadIO (GHandler sub master) 
MonadLift (GHandler sub master) (GWidget sub master) 
~ * master master' => SubsiteGetter (master -> sub) (GHandler anySub master') sub 
(~ * anySub anySub', ~ * master master') => SubsiteGetter (GHandler anySub master sub) (GHandler anySub' master') sub 

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 -> Text)Source

Get the URL rendering function.

getUrlRenderParams :: GHandler sub master (Route master -> [(Text, Text)] -> Text)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.

waiRequest :: GHandler sub master RequestSource

Get the request's Request value.

Special responses

Redirecting

class RedirectUrl master a whereSource

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

Methods

toTextUrl :: a -> GHandler sub master 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) 
(~ * key Text, ~ * val Text) => RedirectUrl master (Route master, [(key, val)]) 

redirect :: RedirectUrl master url => url -> GHandler sub master 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 :: RedirectUrl master url => Status -> url -> GHandler sub master aSource

Redirect to the given URL with the specified status code.

redirectToPost :: RedirectUrl master url => url -> GHandler sub master 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.

Errors

notFound :: GHandler sub master aSource

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

badMethod :: GHandler sub master aSource

Return a 405 method not supported page.

permissionDenied :: Text -> GHandler sub master aSource

Return a 403 permission denied page.

permissionDeniedI :: RenderMessage master msg => msg -> GHandler sub master aSource

Return a 403 permission denied page.

invalidArgs :: [Text] -> GHandler sub master aSource

Return a 400 invalid arguments page.

invalidArgsI :: RenderMessage y msg => [msg] -> GHandler s y 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.

sendFilePartSource

Arguments

:: ContentType 
-> FilePath 
-> Integer

offset

-> Integer

count

-> GHandler sub master a 

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

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

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

sendResponseStatus :: HasReps c => Status -> c -> GHandler s m aSource

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

sendResponseCreated :: Route m -> GHandler s m aSource

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

sendWaiResponse :: Response -> GHandler s 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.

Setting headers

setCookie :: SetCookie -> GHandler sub master ()Source

Set the cookie on the client.

getExpiresSource

Arguments

:: Int

minutes

-> IO UTCTime 

Helper function for setCookieExpires value

deleteCookieSource

Arguments

:: Text

key

-> Text

path

-> GHandler sub master () 

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.

setHeader :: Text -> Text -> GHandler sub master ()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.

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

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

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

lookupSession :: Text -> GHandler s m (Maybe Text)Source

Lookup for session data.

lookupSessionBS :: Text -> GHandler s m (Maybe ByteString)Source

Lookup for session data in binary format.

getSession :: GHandler sub master SessionMapSource

Get all session variables.

setSessionSource

Arguments

:: Text

key

-> Text

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.

setSessionBS :: Text -> ByteString -> GHandler sub master ()Source

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

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

Unsets a session variable. See setSession.

clearSession :: GHandler sub master ()Source

Clear all session variables.

Since: 1.0.1

Ultimate destination

setUltDest :: RedirectUrl master url => url -> 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.

setUltDestCurrent :: 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.

setUltDestReferer :: GHandler sub master ()Source

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

This function will not overwrite an existing ultdest.

redirectUltDestSource

Arguments

:: RedirectUrl master url 
=> url

default destination if nothing in session

-> GHandler sub master 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 :: GHandler sub master ()Source

Remove a previously set ultimate destination. See setUltDest.

Messages

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

Sets a message in the user's session.

See getMessage.

setMessageI :: RenderMessage y msg => msg -> GHandler sub y ()Source

Sets a message in the user's session.

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.

Helpers for specific content

Hamlet

hamletToContent :: HtmlUrl (Route master) -> GHandler sub master ContentSource

Converts the given Hamlet template into Content, which can be used in a Yesod Response.

hamletToRepHtml :: HtmlUrl (Route master) -> GHandler sub master RepHtmlSource

Wraps the Content generated by hamletToContent in a RepHtml.

Misc

newIdent :: GHandler sub master TextSource

Get a unique identifier.

Lifting

class MonadLift base m | m -> base whereSource

The standard MonadTrans class only allows lifting for monad transformers. While GHandler and GWidget should allow lifting, their types do not express that they actually are transformers. This replacement class accounts for this.

Methods

lift :: base a -> m aSource

Instances

(Monad m, MonadTrans t) => MonadLift m (t m) 
MonadLift (ResourceT IO) (GHandler sub master) 
MonadLift (GHandler sub master) (GWidget sub master) 

handlerToIO :: MonadIO m => GHandler sub master (GHandler sub master a -> m a)Source

Returns a function that runs GHandler actions inside IO.

Sometimes you want to run an inner GHandler action outside the control flow of an HTTP request (on the outer GHandler 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).

i18n

getMessageRender :: RenderMessage master message => GHandler s master (message -> Text)Source

Per-request caching

mkCacheKey :: Q ExpSource

Generate a new CacheKey. Be sure to give a full type signature.

cacheLookup :: CacheKey a -> GHandler sub master (Maybe a)Source

cacheInsert :: CacheKey a -> a -> GHandler sub master ()Source

Internal Yesod

runHandler :: HasReps c => GHandler sub master c -> (Route master -> [(Text, Text)] -> Text) -> Maybe (Route sub) -> (Route sub -> Route master) -> master -> sub -> (Word64 -> FileUpload) -> (Loc -> LogLevel -> LogStr -> IO ()) -> 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.

runSubsiteGetter :: SubsiteGetter g m s => g -> m sSource

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

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

toMasterHandlerDyn :: (Route sub -> Route master) -> GHandler sub' master sub -> Route sub -> GHandler sub master a -> GHandler sub' master aSource

FIXME do we need this?

toMasterHandlerMaybe :: (Route sub -> Route master) -> (master -> sub) -> Maybe (Route sub) -> GHandler sub master a -> GHandler sub' master aSource

data HandlerData sub master Source

data ErrorResponse Source

Responses to indicate some form of an error occurred. These are different from SpecialResponse in that they allow for custom error pages.

handlerToYARSource

Arguments

:: (HasReps a, HasReps b) 
=> master

master site foundation

-> sub

sub site foundation

-> (Word64 -> FileUpload) 
-> (Loc -> LogLevel -> LogStr -> IO ()) 
-> (Route sub -> Route master) 
-> (Route master -> [(Text, Text)] -> Text) 
-> (ErrorResponse -> GHandler sub master a) 
-> Request 
-> Maybe (Route sub) 
-> SessionMap 
-> GHandler sub master b 
-> ResourceT IO YesodAppResult 

headerToPair :: Header -> (CI ByteString, ByteString)Source

Convert Header to a key/value pair.