- type family Route a
- class YesodSubRoute s y where
- fromSubRoute :: s -> y -> Route s -> Route y
- type GHandler sub master = GGHandler sub master (Iteratee ByteString IO)
- data GGHandler sub master m a
- getYesod :: Monad m => GGHandler sub master m master
- getYesodSub :: Monad m => GGHandler sub master m sub
- getUrlRender :: Monad m => GGHandler sub master m (Route master -> String)
- getUrlRenderParams :: Monad m => GGHandler sub master m (Route master -> [(String, String)] -> String)
- getCurrentRoute :: Monad m => GGHandler sub master m (Maybe (Route sub))
- getRouteToMaster :: Monad m => GGHandler sub master m (Route sub -> Route master)
- data RedirectType
- redirect :: Monad mo => RedirectType -> Route master -> GGHandler sub master mo a
- redirectParams :: Monad mo => RedirectType -> Route master -> [(String, String)] -> GGHandler sub master mo a
- redirectString :: Monad mo => RedirectType -> ByteString -> GGHandler sub master mo a
- redirectToPost :: Monad mo => Route master -> GGHandler sub master mo a
- notFound :: Failure ErrorResponse m => m a
- badMethod :: (RequestReader m, Failure ErrorResponse m) => m a
- permissionDenied :: Failure ErrorResponse m => String -> m a
- invalidArgs :: Failure ErrorResponse m => [String] -> m a
- sendFile :: Monad mo => ContentType -> FilePath -> GGHandler sub master mo a
- sendResponse :: (Monad mo, HasReps c) => c -> GGHandler sub master mo a
- sendResponseStatus :: (Monad mo, HasReps c) => Status -> c -> GGHandler s m mo a
- sendResponseCreated :: Monad mo => Route m -> GGHandler s m mo a
- sendWaiResponse :: Monad mo => Response -> GGHandler s m mo b
- setCookie :: Monad mo => Int -> ByteString -> ByteString -> GGHandler sub master mo ()
- deleteCookie :: Monad mo => ByteString -> GGHandler sub master mo ()
- setHeader :: Monad mo => ResponseHeader -> ByteString -> GGHandler sub master mo ()
- setLanguage :: Monad mo => String -> GGHandler sub master mo ()
- cacheSeconds :: Monad mo => Int -> GGHandler s m mo ()
- neverExpires :: Monad mo => GGHandler s m mo ()
- alreadyExpired :: Monad mo => GGHandler s m mo ()
- expiresAt :: Monad mo => UTCTime -> GGHandler s m mo ()
- type SessionMap = Map String String
- lookupSession :: Monad mo => ParamName -> GGHandler s m mo (Maybe ParamValue)
- getSession :: Monad mo => GGHandler s m mo SessionMap
- setSession :: Monad mo => String -> String -> GGHandler sub master mo ()
- deleteSession :: Monad mo => String -> GGHandler sub master mo ()
- setUltDest :: Monad mo => Route master -> GGHandler sub master mo ()
- setUltDestString :: Monad mo => String -> GGHandler sub master mo ()
- setUltDest' :: Monad mo => GGHandler sub master mo ()
- redirectUltDest :: Monad mo => RedirectType -> Route master -> GGHandler sub master mo ()
- setMessage :: Monad mo => Html -> GGHandler sub master mo ()
- getMessage :: Monad mo => GGHandler sub master mo (Maybe Html)
- hamletToContent :: Monad mo => Hamlet (Route master) -> GGHandler sub master mo Content
- hamletToRepHtml :: Monad mo => Hamlet (Route master) -> GGHandler sub master mo RepHtml
- newIdent :: Monad mo => GGHandler sub master mo String
- liftIOHandler :: MonadIO mo => GGHandler sub master IO a -> GGHandler sub master mo a
- runHandler :: HasReps c => GHandler sub master c -> (Route master -> [(String, String)] -> String) -> Maybe (Route sub) -> (Route sub -> Route master) -> master -> sub -> YesodApp
- newtype YesodApp = YesodApp {
- unYesodApp :: (ErrorResponse -> YesodApp) -> Request -> [ContentType] -> SessionMap -> Iteratee ByteString IO YesodAppResult
- runSubsiteGetter :: SubsiteGetter g m s => g -> m s
- toMasterHandler :: (Route sub -> Route master) -> (master -> sub) -> Route sub -> GGHandler sub master mo a -> GGHandler sub' master mo a
- toMasterHandlerDyn :: Monad mo => (Route sub -> Route master) -> GGHandler sub' master mo sub -> Route sub -> GGHandler sub master mo a -> GGHandler sub' master mo a
- toMasterHandlerMaybe :: (Route sub -> Route master) -> (master -> sub) -> Maybe (Route sub) -> GGHandler sub master mo a -> GGHandler sub' master mo a
- localNoCurrent :: Monad mo => GGHandler s m mo a -> GGHandler s m mo a
- data HandlerData sub master
- data ErrorResponse
- data YesodAppResult
- = YARWai Response
- | YARPlain Status [Header] ContentType Content SessionMap
- handlerToYAR :: (HasReps a, HasReps b) => m -> s -> (Route s -> Route m) -> (Route m -> [(String, String)] -> String) -> (ErrorResponse -> GHandler s m a) -> Request -> Maybe (Route s) -> SessionMap -> GHandler s m b -> Iteratee ByteString IO YesodAppResult
- yarToResponse :: HeaderRenderer -> YesodAppResult -> Response
- headerToPair :: (Int -> UTCTime) -> Header -> (ResponseHeader, ByteString)
Type families
class YesodSubRoute s y whereSource
fromSubRoute :: s -> y -> Route s -> Route ySource
Handler monad
data GGHandler sub master m 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.
Monad monad => Failure ErrorResponse (GGHandler sub master monad) | |
MonadTransPeel (GGHandler s m) | |
MonadTrans (GGHandler s m) | |
Monad m => Monad (GGHandler sub master m) | |
Functor m => Functor (GGHandler sub master m) | |
(Monad m, Functor m) => Applicative (GGHandler sub master m) | |
MonadPeelIO m => MonadPeelIO (GGHandler sub master m) | |
MonadIO m => MonadIO (GGHandler sub master m) |
Read information from handler
getYesodSub :: Monad m => GGHandler sub master m subSource
Get the sub application argument.
getUrlRender :: Monad m => GGHandler sub master m (Route master -> String)Source
Get the URL rendering function.
getUrlRenderParams :: Monad m => GGHandler sub master m (Route master -> [(String, String)] -> String)Source
The URL rendering function with query-string parameters.
getCurrentRoute :: Monad m => GGHandler sub master m (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 :: Monad m => GGHandler sub master m (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 :: Monad mo => RedirectType -> Route master -> GGHandler sub master mo aSource
Redirect to the given route.
redirectParams :: Monad mo => RedirectType -> Route master -> [(String, String)] -> GGHandler sub master mo aSource
Redirects to the given route with the associated query-string parameters.
redirectString :: Monad mo => RedirectType -> ByteString -> GGHandler sub master mo aSource
Redirect to the given URL.
redirectToPost :: Monad mo => Route master -> GGHandler sub master mo 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 :: 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 :: Monad mo => ContentType -> FilePath -> GGHandler sub master mo 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 :: (Monad mo, HasReps c) => c -> GGHandler sub master mo aSource
Bypass remaining handler code and output the given content with a 200 status code.
sendResponseStatus :: (Monad mo, HasReps c) => Status -> c -> GGHandler s m mo aSource
Bypass remaining handler code and output the given content with the given status code.
sendResponseCreated :: Monad mo => Route m -> GGHandler s m mo aSource
Send a 201 Created response with the given route as the Location response header.
sendWaiResponse :: Monad mo => Response -> GGHandler s m mo 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
:: Monad mo | |
=> Int | minutes to timeout |
-> ByteString | key |
-> ByteString | value |
-> GGHandler sub master mo () |
Set the cookie on the client.
deleteCookie :: Monad mo => ByteString -> GGHandler sub master mo ()Source
Unset the cookie on the client.
setHeader :: Monad mo => ResponseHeader -> ByteString -> GGHandler sub master mo ()Source
Set an arbitrary response header.
setLanguage :: Monad mo => String -> GGHandler sub master mo ()Source
Set the language in the user session. Will show up in languages
on the
next request.
Content caching and expiration
cacheSeconds :: Monad mo => Int -> GGHandler s m mo ()Source
Set the Cache-Control header to indicate this response should be cached for the given number of seconds.
neverExpires :: Monad mo => GGHandler s m mo ()Source
Set the Expires header to some date in 2037. In other words, this content is never (realistically) expired.
alreadyExpired :: Monad mo => GGHandler s m mo ()Source
Set an Expires header in the past, meaning this content should not be cached.
expiresAt :: Monad mo => UTCTime -> GGHandler s m mo ()Source
Set an Expires header to the given date.
Session
type SessionMap = Map String StringSource
lookupSession :: Monad mo => ParamName -> GGHandler s m mo (Maybe ParamValue)Source
Lookup for session data.
getSession :: Monad mo => GGHandler s m mo SessionMapSource
Get all session variables.
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 :: Monad mo => String -> GGHandler sub master mo ()Source
Unsets a session variable. See setSession
.
Ultimate destination
setUltDest :: Monad mo => Route master -> GGHandler sub master mo ()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 :: Monad mo => String -> GGHandler sub master mo ()Source
Same as setUltDest
, but use the given string.
setUltDest' :: Monad mo => GGHandler sub master mo ()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.
:: Monad mo | |
=> RedirectType | |
-> Route master | default destination if nothing in session |
-> GGHandler sub master mo () |
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 :: Monad mo => Html -> GGHandler sub master mo ()Source
Sets a message in the user's session.
See getMessage
.
getMessage :: Monad mo => GGHandler sub master mo (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 :: Monad mo => Hamlet (Route master) -> GGHandler sub master mo ContentSource
Converts the given Hamlet template into Content
, which can be used in a
Yesod Response
.
hamletToRepHtml :: Monad mo => Hamlet (Route master) -> GGHandler sub master mo RepHtmlSource
Wraps the Content
generated by hamletToContent
in a RepHtml
.
Misc
Internal Yesod
runHandler :: HasReps c => GHandler sub master c -> (Route master -> [(String, String)] -> String) -> Maybe (Route sub) -> (Route sub -> Route 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.
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.
YesodApp | |
|
runSubsiteGetter :: SubsiteGetter g m s => g -> m sSource
toMasterHandler :: (Route sub -> Route master) -> (master -> sub) -> Route sub -> GGHandler sub master mo a -> GGHandler sub' master mo aSource
Used internally for promoting subsite handler functions to master site handler functions. Should not be needed by users.
toMasterHandlerDyn :: Monad mo => (Route sub -> Route master) -> GGHandler sub' master mo sub -> Route sub -> GGHandler sub master mo a -> GGHandler sub' master mo aSource
toMasterHandlerMaybe :: (Route sub -> Route master) -> (master -> sub) -> Maybe (Route sub) -> GGHandler sub master mo a -> GGHandler sub' master mo aSource
localNoCurrent :: Monad mo => GGHandler s m mo a -> GGHandler s m mo 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.
Eq ErrorResponse | |
Show ErrorResponse | |
Typeable ErrorResponse | |
Exception ErrorResponse | |
Monad monad => Failure ErrorResponse (GGHandler sub master monad) |
data YesodAppResult Source
YARWai Response | |
YARPlain Status [Header] ContentType Content SessionMap |
:: (HasReps a, HasReps b) | |
=> m | master site foundation |
-> s | sub site foundation |
-> (Route s -> Route m) | |
-> (Route m -> [(String, String)] -> String) | url render |
-> (ErrorResponse -> GHandler s m a) | |
-> Request | |
-> Maybe (Route s) | |
-> SessionMap | |
-> GHandler s m b | |
-> Iteratee ByteString IO YesodAppResult |
yarToResponse :: HeaderRenderer -> YesodAppResult -> ResponseSource
:: (Int -> UTCTime) | minutes -> expiration time |
-> Header | |
-> (ResponseHeader, ByteString) |
Convert Header to a key/value pair.