Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class RenderRoute site => Yesod site where
- approot :: Approot site
- errorHandler :: ErrorResponse -> HandlerFor site TypedContent
- defaultLayout :: WidgetFor site () -> HandlerFor site Html
- urlParamRenderOverride :: site -> Route site -> [(Text, Text)] -> Maybe Builder
- isAuthorized :: Route site -> Bool -> HandlerFor site AuthResult
- isWriteRequest :: Route site -> HandlerFor site Bool
- authRoute :: site -> Maybe (Route site)
- cleanPath :: site -> [Text] -> Either [Text] [Text]
- joinPath :: site -> Text -> [Text] -> [(Text, Text)] -> Builder
- addStaticContent :: Text -> Text -> ByteString -> HandlerFor site (Maybe (Either Text (Route site, [(Text, Text)])))
- maximumContentLength :: site -> Maybe (Route site) -> Maybe Word64
- maximumContentLengthIO :: site -> Maybe (Route site) -> IO (Maybe Word64)
- makeLogger :: site -> IO Logger
- messageLoggerSource :: site -> Logger -> Loc -> LogSource -> LogLevel -> LogStr -> IO ()
- jsLoader :: site -> ScriptLoadPosition site
- jsAttributes :: site -> [(Text, Text)]
- jsAttributesHandler :: HandlerFor site [(Text, Text)]
- makeSessionBackend :: site -> IO (Maybe SessionBackend)
- fileUpload :: site -> RequestBodyLength -> FileUpload
- shouldLogIO :: site -> LogSource -> LogLevel -> IO Bool
- yesodMiddleware :: ToTypedContent res => HandlerFor site res -> HandlerFor site res
- yesodWithInternalState :: site -> Maybe (Route site) -> (InternalState -> IO a) -> IO a
- defaultMessageWidget :: Html -> HtmlUrl (Route site) -> WidgetFor site ()
- class Yesod site => YesodDispatch site where
- yesodDispatch :: YesodRunnerEnv site -> Application
- class YesodSubDispatch sub master where
- yesodSubDispatch :: YesodSubRunnerEnv sub master -> Application
- class Eq (Route a) => RenderRoute a where
- class RenderRoute a => ParseRoute a where
- class RenderRoute a => RouteAttrs a where
- routeAttrs :: Route a -> Set Text
- class YesodBreadcrumbs site where
- breadcrumb :: Route site -> HandlerFor site (Text, Maybe (Route site))
- breadcrumbs :: (YesodBreadcrumbs site, Show (Route site), Eq (Route site)) => HandlerFor site (Text, [(Route site, Text)])
- data Approot master
- = ApprootRelative
- | ApprootStatic !Text
- | ApprootMaster !(master -> Text)
- | ApprootRequest !(master -> Request -> Text)
- data FileUpload
- = FileUploadMemory !(BackEnd ByteString)
- | FileUploadDisk !(InternalState -> BackEnd FilePath)
- | FileUploadSource !(BackEnd (ConduitT () ByteString (ResourceT IO) ()))
- data ErrorResponse
- maybeAuthorized :: Yesod site => Route site -> Bool -> HandlerT site IO (Maybe (Route site))
- widgetToPageContent :: Yesod site => WidgetFor site () -> HandlerFor site (PageContent (Route site))
- defaultErrorHandler :: Yesod site => ErrorResponse -> HandlerFor site TypedContent
- defaultYesodMiddleware :: Yesod site => HandlerFor site res -> HandlerFor site res
- authorizationCheck :: Yesod site => HandlerFor site ()
- data AuthResult
- unauthorizedI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => msg -> m AuthResult
- defaultMakeLogger :: IO Logger
- defaultMessageLoggerSource :: (LogSource -> LogLevel -> IO Bool) -> Logger -> Loc -> LogSource -> LogLevel -> LogStr -> IO ()
- defaultShouldLogIO :: LogSource -> LogLevel -> IO Bool
- formatLogMessage :: IO ZonedDate -> Loc -> LogSource -> LogLevel -> LogStr -> IO LogStr
- data LogLevel
- logDebug :: Q Exp
- logInfo :: Q Exp
- logWarn :: Q Exp
- logError :: Q Exp
- logOther :: Text -> Q Exp
- logDebugS :: Q Exp
- logInfoS :: Q Exp
- logWarnS :: Q Exp
- logErrorS :: Q Exp
- logOtherS :: Q Exp
- newtype SessionBackend = SessionBackend {
- sbLoadSession :: Request -> IO (SessionMap, SaveSession)
- customizeSessionCookies :: (SetCookie -> SetCookie) -> SessionBackend -> SessionBackend
- defaultClientSessionBackend :: Int -> FilePath -> IO SessionBackend
- envClientSessionBackend :: Int -> String -> IO SessionBackend
- clientSessionBackend :: Key -> IO ClientSessionDateCache -> SessionBackend
- sslOnlySessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend)
- laxSameSiteSessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend)
- strictSameSiteSessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend)
- sslOnlyMiddleware :: Int -> HandlerFor site res -> HandlerFor site res
- clientSessionDateCacher :: NominalDiffTime -> IO (IO ClientSessionDateCache, IO ())
- loadClientSession :: Key -> IO ClientSessionDateCache -> ByteString -> Request -> IO (SessionMap, SaveSession)
- data Header
- defaultCsrfMiddleware :: Yesod site => HandlerFor site res -> HandlerFor site res
- defaultCsrfSetCookieMiddleware :: HandlerFor site res -> HandlerFor site res
- csrfSetCookieMiddleware :: HandlerFor site res -> SetCookie -> HandlerFor site res
- defaultCsrfCheckMiddleware :: Yesod site => HandlerFor site res -> HandlerFor site res
- csrfCheckMiddleware :: HandlerFor site res -> HandlerFor site Bool -> CI ByteString -> Text -> HandlerFor site res
- data ScriptLoadPosition master
- = BottomOfBody
- | BottomOfHeadBlocking
- | BottomOfHeadAsync !(BottomOfHeadAsync master)
- type BottomOfHeadAsync master = [Text] -> Maybe (HtmlUrl (Route master)) -> HtmlUrl (Route master)
- class (MonadResource m, MonadLogger m) => MonadHandler m where
- type HandlerSite m
- type SubHandlerSite m
- liftHandler :: HandlerFor (HandlerSite m) a -> m a
- liftSubHandler :: SubHandlerFor (SubHandlerSite m) (HandlerSite m) a -> m a
- class MonadHandler m => MonadWidget m where
- liftWidget :: WidgetFor (HandlerSite m) a -> m a
- guessApproot :: Approot site
- guessApprootOr :: Approot site -> Approot site
- getApprootText :: Approot site -> site -> Request -> Text
- yesodVersion :: String
- yesodRender :: Yesod y => y -> ResolvedApproot -> Route y -> [(Text, Text)] -> Text
- runFakeHandler :: (Yesod site, MonadIO m) => SessionMap -> (site -> Logger) -> site -> HandlerT site IO a -> m (Either ErrorResponse a)
- newtype LiteApp = LiteApp {
- unLiteApp :: Method -> [Text] -> Maybe (LiteHandler TypedContent)
- type LiteHandler = HandlerFor LiteApp
- type LiteWidget = WidgetFor LiteApp
- liteApp :: Writer LiteApp () -> LiteApp
- dispatchTo :: ToTypedContent a => LiteHandler a -> Writer LiteApp ()
- onMethod :: Method -> Writer LiteApp () -> Writer LiteApp ()
- onStatic :: Text -> Writer LiteApp () -> Writer LiteApp ()
- withDynamic :: PathPiece p => (p -> Writer LiteApp ()) -> Writer LiteApp ()
- withDynamicMulti :: PathMultiPiece ps => (ps -> Writer LiteApp ()) -> Writer LiteApp ()
- yesodRunner :: (ToTypedContent res, Yesod site) => HandlerFor site res -> YesodRunnerEnv site -> Maybe (Route site) -> Application
- module Yesod.Core.Content
- module Yesod.Core.Dispatch
- module Yesod.Core.Handler
- module Yesod.Core.Widget
- module Yesod.Core.Json
- module Text.Shakespeare.I18N
- formatW3 :: UTCTime -> Text
- formatRFC1123 :: UTCTime -> Text
- formatRFC822 :: UTCTime -> Text
- preEscapedToMarkup :: ToMarkup a => a -> Markup
- toHtml :: ToMarkup a => a -> Html
- type Html = Markup
- class MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- class Monad m => MonadIO (m :: Type -> Type) where
- class MonadIO m => MonadUnliftIO (m :: Type -> Type) where
- withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b
- class MonadIO m => MonadResource (m :: Type -> Type) where
- liftResourceT :: ResourceT IO a -> m a
- class Monad m => MonadLogger (m :: Type -> Type)
- type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
- showIntegral :: Integral a => a -> String
- readIntegral :: Num a => String -> Maybe a
- hamlet :: QuasiQuoter
- shamlet :: QuasiQuoter
- xhamlet :: QuasiQuoter
- type HtmlUrl url = Render url -> Html
- julius :: QuasiQuoter
- type JavascriptUrl url = (url -> [(Text, Text)] -> Text) -> Javascript
- renderJavascriptUrl :: (url -> [(Text, Text)] -> Text) -> JavascriptUrl url -> Text
- cassius :: QuasiQuoter
- lucius :: QuasiQuoter
- type CssUrl url = (url -> [(Text, Text)] -> Text) -> Css
- renderCssUrl :: (url -> [(Text, Text)] -> Text) -> CssUrl url -> Text
Type classes
class RenderRoute site => Yesod site where Source #
Define settings for a Yesod applications. All methods have intelligent defaults, and therefore no implementation is required.
Nothing
approot :: Approot site Source #
An absolute URL to the root of the application. Do not include trailing slash.
Default value: guessApproot
. If you know your application root
statically, it will be more efficient and more reliable to instead use
ApprootStatic
or ApprootMaster
. If you do not need full absolute
URLs, you can use ApprootRelative
instead.
Note: Prior to yesod-core 1.5, the default value was ApprootRelative
.
errorHandler :: ErrorResponse -> HandlerFor site TypedContent Source #
Output error response pages.
Default value: defaultErrorHandler
.
defaultLayout :: WidgetFor site () -> HandlerFor site Html Source #
Applies some form of layout to the contents of a page.
urlParamRenderOverride Source #
Override the rendering function for a particular URL and query string parameters. One use case for this is to offload static hosting to a different domain name to avoid sending cookies.
For backward compatibility default implementation is in terms of
urlRenderOverride
, probably ineffective
Since 1.4.23
:: Route site | |
-> Bool | is this a write request? |
-> HandlerFor site AuthResult |
Determine if a request is authorized or not.
Return Authorized
if the request is authorized,
Unauthorized
a message if unauthorized.
If authentication is required, return AuthenticationRequired
.
isWriteRequest :: Route site -> HandlerFor site Bool Source #
Determines whether the current request is a write request. By default, this assumes you are following RESTful principles, and determines this from request method. In particular, all except the following request methods are considered write: GET HEAD OPTIONS TRACE.
This function is used to determine if a request is authorized; see
isAuthorized
.
authRoute :: site -> Maybe (Route site) Source #
The default route for authentication.
Used in particular by isAuthorized
, but library users can do whatever
they want with it.
cleanPath :: site -> [Text] -> Either [Text] [Text] Source #
A function used to clean up path segments. It returns Right
with a
clean path or Left
with a new set of pieces the user should be
redirected to. The default implementation enforces:
- No double slashes
- There is no trailing slash.
Note that versions of Yesod prior to 0.7 used a different set of rules involing trailing slashes.
Builds an absolute URL by concatenating the application root with the
pieces of a path and a query string, if any.
Note that the pieces of the path have been previously cleaned up by cleanPath
.
:: Text | filename extension |
-> Text | mime-type |
-> ByteString | content |
-> HandlerFor site (Maybe (Either Text (Route site, [(Text, Text)]))) |
This function is used to store some static content to be served as an external file. The most common case of this is stashing CSS and JavaScript content in an external file; the Yesod.Widget module uses this feature.
The return value is Nothing
if no storing was performed; this is the
default implementation. A Just
Left
gives the absolute URL of the
file, whereas a Just
Right
gives the type-safe URL. The former is
necessary when you are serving the content outside the context of a
Yesod application, such as via memcached.
maximumContentLength :: site -> Maybe (Route site) -> Maybe Word64 Source #
Maximum allowed length of the request body, in bytes.
This method may be ignored if maximumContentLengthIO
is overridden.
If Nothing
, no maximum is applied.
Default: 2 megabytes.
maximumContentLengthIO :: site -> Maybe (Route site) -> IO (Maybe Word64) Source #
Maximum allowed length of the request body, in bytes. This is similar
to maximumContentLength
, but the result lives in IO
. This allows
you to dynamically change the maximum file size based on some external
source like a database or an IORef
.
The default implementation uses maximumContentLength
. Future version of yesod will
remove maximumContentLength
and use this method exclusively.
Since: 1.6.13
makeLogger :: site -> IO Logger Source #
Creates a Logger
to use for log messages.
Note that a common technique (endorsed by the scaffolding) is to create
a Logger
value and place it in your foundation datatype, and have this
method return that already created value. That way, you can use that
same Logger
for printing messages during app initialization.
Default: the defaultMakeLogger
function.
Send a message to the Logger
provided by getLogger
.
Default: the defaultMessageLoggerSource
function, using
shouldLogIO
to check whether we should log.
jsLoader :: site -> ScriptLoadPosition site Source #
Where to Load sripts from. We recommend the default value,
BottomOfBody
.
jsAttributes :: site -> [(Text, Text)] Source #
Default attributes to put on the JavaScript script tag generated for julius files
jsAttributesHandler :: HandlerFor site [(Text, Text)] Source #
Same as jsAttributes
but allows you to run arbitrary Handler code
This is useful if you need to add a randomised nonce value to the script
tag generated by widgetFile
. If this function is overridden then
jsAttributes
is ignored.
Since: 1.6.16
makeSessionBackend :: site -> IO (Maybe SessionBackend) Source #
Create a session backend. Returning Nothing
disables
sessions. If you'd like to change the way that the session
cookies are created, take a look at
customizeSessionCookies
.
Default: Uses clientsession with a 2 hour timeout.
fileUpload :: site -> RequestBodyLength -> FileUpload Source #
How to store uploaded files.
Default: When the request body is greater than 50kb, store in a temp file. For chunked request bodies, store in a temp file. Otherwise, store in memory.
shouldLogIO :: site -> LogSource -> LogLevel -> IO Bool Source #
Should we log the given log source/level combination.
Default: the defaultShouldLogIO
function.
Since 1.2.4
yesodMiddleware :: ToTypedContent res => HandlerFor site res -> HandlerFor site res Source #
A Yesod middleware, which will wrap every handler function. This allows you to run code before and after a normal handler.
Default: the defaultYesodMiddleware
function.
Since: 1.1.6
yesodWithInternalState :: site -> Maybe (Route site) -> (InternalState -> IO a) -> IO a Source #
How to allocate an InternalState
for each request.
The default implementation is almost always what you want. However, if
you know that you are never taking advantage of the MonadResource
instance in your handler functions, setting this to a dummy
implementation can provide a small optimization. Only do this if you
really know what you're doing, otherwise you can turn safe code into a
runtime error!
Since 1.4.2
defaultMessageWidget :: Html -> HtmlUrl (Route site) -> WidgetFor site () Source #
Convert a title and HTML snippet into a Widget
. Used
primarily for wrapping up error messages for better display.
Since: 1.4.30
Instances
class Yesod site => YesodDispatch site where Source #
This class is automatically instantiated when you use the template haskell mkYesod function. You should never need to deal with it directly.
yesodDispatch :: YesodRunnerEnv site -> Application Source #
Instances
YesodDispatch LiteApp Source # | |
Defined in Yesod.Core.Internal.LiteApp |
class YesodSubDispatch sub master where Source #
yesodSubDispatch :: YesodSubRunnerEnv sub master -> Application Source #
Instances
YesodSubDispatch WaiSubsiteWithAuth master Source # | |
Defined in Yesod.Core.Class.Dispatch yesodSubDispatch :: YesodSubRunnerEnv WaiSubsiteWithAuth master -> Application Source # | |
YesodSubDispatch WaiSubsite master Source # | |
Defined in Yesod.Core.Class.Dispatch yesodSubDispatch :: YesodSubRunnerEnv WaiSubsite master -> Application Source # |
class Eq (Route a) => RenderRoute a where Source #
The type-safe URLs associated with a site argument.
Instances
RenderRoute WaiSubsiteWithAuth Source # | |
Defined in Yesod.Core.Types data Route WaiSubsiteWithAuth Source # renderRoute :: Route WaiSubsiteWithAuth -> ([Text], [(Text, Text)]) Source # | |
RenderRoute WaiSubsite Source # | |
Defined in Yesod.Core.Types data Route WaiSubsite Source # renderRoute :: Route WaiSubsite -> ([Text], [(Text, Text)]) Source # | |
RenderRoute LiteApp Source # | |
class RenderRoute a => ParseRoute a where Source #
Instances
ParseRoute WaiSubsiteWithAuth Source # | |
Defined in Yesod.Core.Types parseRoute :: ([Text], [(Text, Text)]) -> Maybe (Route WaiSubsiteWithAuth) Source # | |
ParseRoute WaiSubsite Source # | |
Defined in Yesod.Core.Types parseRoute :: ([Text], [(Text, Text)]) -> Maybe (Route WaiSubsite) Source # | |
ParseRoute LiteApp Source # | |
Defined in Yesod.Core.Internal.LiteApp |
class RenderRoute a => RouteAttrs a where Source #
:: Route a | |
-> Set Text | A set of attributes associated with the route. |
Breadcrumbs
class YesodBreadcrumbs site where Source #
A type-safe, concise method of creating breadcrumbs for pages. For each resource, you declare the title of the page and the parent resource (if present).
breadcrumb :: Route site -> HandlerFor site (Text, Maybe (Route site)) Source #
Returns the title and the parent resource, if available. If you return
a Nothing
, then this is considered a top-level page.
breadcrumbs :: (YesodBreadcrumbs site, Show (Route site), Eq (Route site)) => HandlerFor site (Text, [(Route site, Text)]) Source #
Gets the title of the current page and the hierarchy of parent pages, along with their respective titles.
Types
How to determine the root of the application for constructing URLs.
Note that future versions of Yesod may add new constructors without bumping
the major version number. As a result, you should not pattern match on
Approot
values.
ApprootRelative | No application root. |
ApprootStatic !Text | |
ApprootMaster !(master -> Text) | |
ApprootRequest !(master -> Request -> Text) |
data FileUpload Source #
FileUploadMemory !(BackEnd ByteString) | |
FileUploadDisk !(InternalState -> BackEnd FilePath) | |
FileUploadSource !(BackEnd (ConduitT () ByteString (ResourceT IO) ())) |
data ErrorResponse Source #
Responses to indicate some form of an error occurred.
NotFound | The requested resource was not found.
Examples of when this occurs include when an incorrect URL is used, or |
InternalError !Text | Some sort of unexpected exception.
If your application uses |
InvalidArgs ![Text] | Indicates some sort of invalid or missing argument, like a missing query parameter or malformed JSON body.
Examples Yesod functions that send this include |
NotAuthenticated | Indicates the user is not logged in.
This is thrown when |
PermissionDenied !Text | Indicates the user doesn't have permission to access the requested resource.
This is thrown when |
BadMethod !Method | Indicates the URL would have been valid if used with a different HTTP method (e.g. a GET was used, but only POST is handled.) HTTP code: 405. |
Instances
Utilities
Return the same URL if the user is authorized to see it.
Built on top of isAuthorized
. This is useful for building page that only
contain links to pages the user is allowed to see.
widgetToPageContent :: Yesod site => WidgetFor site () -> HandlerFor site (PageContent (Route site)) Source #
Convert a widget to a PageContent
.
Defaults
defaultErrorHandler :: Yesod site => ErrorResponse -> HandlerFor site TypedContent Source #
The default error handler for errorHandler
.
defaultYesodMiddleware :: Yesod site => HandlerFor site res -> HandlerFor site res Source #
Default implementation of yesodMiddleware
. Adds the response header
"Vary: Accept, Accept-Language", "X-XSS-Protection: 1; mode=block", and
performs authorization checks.
Since 1.2.0
authorizationCheck :: Yesod site => HandlerFor site () Source #
Check if a given request is authorized via isAuthorized
and
isWriteRequest
.
Since 1.2.0
Data types
data AuthResult Source #
Instances
Eq AuthResult Source # | |
Defined in Yesod.Core.Types (==) :: AuthResult -> AuthResult -> Bool # (/=) :: AuthResult -> AuthResult -> Bool # | |
Read AuthResult Source # | |
Defined in Yesod.Core.Types readsPrec :: Int -> ReadS AuthResult # readList :: ReadS [AuthResult] # readPrec :: ReadPrec AuthResult # readListPrec :: ReadPrec [AuthResult] # | |
Show AuthResult Source # | |
Defined in Yesod.Core.Types showsPrec :: Int -> AuthResult -> ShowS # show :: AuthResult -> String # showList :: [AuthResult] -> ShowS # |
unauthorizedI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => msg -> m AuthResult Source #
Return an Unauthorized
value, with the given i18n message.
Logging
defaultMakeLogger :: IO Logger Source #
Default implementation of makeLogger
. Sends to stdout and
automatically flushes on each write.
Since 1.4.10
defaultMessageLoggerSource Source #
:: (LogSource -> LogLevel -> IO Bool) | Check whether we should log this |
-> Logger | |
-> Loc | position in source code |
-> LogSource | |
-> LogLevel | |
-> LogStr | message |
-> IO () |
Default implementation of messageLoggerSource
. Checks if the
message should be logged using the provided function, and if so,
formats using formatLogMessage
. You can use defaultShouldLogIO
as the provided function.
Since 1.4.10
defaultShouldLogIO :: LogSource -> LogLevel -> IO Bool Source #
Default implementation of shouldLog
. Logs everything at or
above LevelInfo
.
Since 1.4.10
Default formatting for log messages. When you use
the template haskell logging functions for to log with information
about the source location, that information will be appended to
the end of the log. When you use the non-TH logging functions,
like logDebugN
, this function does not include source
information. This currently works by checking to see if the
package name is the string "<unknown>". This is a hack,
but it removes some of the visual clutter from non-TH logs.
Since 1.4.10
Generates a function that takes a Text
and logs a LevelDebug
message. Usage:
$(logDebug) "This is a debug log message"
Generates a function that takes a Text
and logs a LevelOther
message. Usage:
$(logOther "My new level") "This is a log message"
Generates a function that takes a LogSource
and Text
and logs a LevelDebug
message. Usage:
$logDebugS "SomeSource" "This is a debug log message"
Generates a function that takes a LogSource
, a level name and a Text
and logs a LevelOther
message. Usage:
$logOtherS "SomeSource" "My new level" "This is a log message"
Sessions
newtype SessionBackend Source #
SessionBackend | |
|
customizeSessionCookies :: (SetCookie -> SetCookie) -> SessionBackend -> SessionBackend Source #
Customize the cookies used by the session backend. You may
use this function on your definition of makeSessionBackend
.
For example, you could set the cookie domain so that it would work across many subdomains:
makeSessionBackend site =
(fmap . fmap) (customizeSessionCookies addDomain) ...
where
addDomain cookie = cookie { setCookieDomain
= Just ".example.com" }
Default: Do not customize anything (id
).
defaultClientSessionBackend Source #
:: Int | minutes |
-> FilePath | key file |
-> IO SessionBackend |
envClientSessionBackend Source #
:: Int | minutes |
-> String | environment variable name |
-> IO SessionBackend |
Create a SessionBackend
which reads the session key from the named
environment variable.
This can be useful if:
- You can't rely on a persistent file system (e.g. Heroku)
- Your application is open source (e.g. you can't commit the key)
By keeping a consistent value in the environment variable, your users will have consistent sessions without relying on the file system.
Note: A suitable value should only be obtained in one of two ways:
- Run this code without the variable set, a value will be generated and
printed on
devstdout/
- Use
clientsession-generate
Since 1.4.5
:: Key | The encryption key |
-> IO ClientSessionDateCache | |
-> SessionBackend |
sslOnlySessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend) Source #
Defends against session hijacking by setting the secure bit on session
cookies so that browsers will not transmit them over http. With this
setting on, it follows that the server will regard requests made over
http as sessionless, because the session cookie will not be included in
the request. Use this as part of a total security measure which also
includes disabling HTTP traffic to the site or issuing redirects from
HTTP urls, and composing sslOnlyMiddleware
with the site's
yesodMiddleware
.
Since 1.4.7
laxSameSiteSessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend) Source #
Helps defend against CSRF attacks by setting the SameSite attribute on session cookies to Lax. With the Lax setting, the cookie will be sent with same-site requests, and with cross-site top-level navigations.
This option is liable to change in future versions of Yesod as the spec evolves. View more information here.
Since: 1.4.23
strictSameSiteSessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend) Source #
Helps defend against CSRF attacks by setting the SameSite attribute on session cookies to Strict. With the Strict setting, the cookie will only be sent with same-site requests.
This option is liable to change in future versions of Yesod as the spec evolves. View more information here.
Since: 1.4.23
:: Int | minutes |
-> HandlerFor site res | |
-> HandlerFor site res |
Apply a Strict-Transport-Security header with the specified timeout to all responses so that browsers will rewrite all http links to https until the timeout expires. For security, the max-age of the STS header should always equal or exceed the client sessions timeout. This defends against SSL-stripping man-in-the-middle attacks. It is only effective if a secure connection has already been made; Strict-Transport-Security headers are ignored over HTTP.
Since 1.4.7
clientSessionDateCacher Source #
:: NominalDiffTime | Inactive session validity. |
-> IO (IO ClientSessionDateCache, IO ()) |
:: Key | |
-> IO ClientSessionDateCache | |
-> ByteString | session name |
-> Request | |
-> IO (SessionMap, SaveSession) |
Headers to be added to a Result
.
AddCookie !SetCookie | |
DeleteCookie !ByteString !ByteString | name and path |
Header !(CI ByteString) !ByteString | key and value |
CSRF protection
defaultCsrfMiddleware :: Yesod site => HandlerFor site res -> HandlerFor site res Source #
Calls defaultCsrfSetCookieMiddleware
and defaultCsrfCheckMiddleware
.
For details, see the "AJAX CSRF protection" section of Yesod.Core.Handler.
You can chain this middleware together with other middleware like so:
yesodMiddleware
=defaultYesodMiddleware
.defaultCsrfMiddleware
or:
yesodMiddleware
app =defaultYesodMiddleware
$defaultCsrfMiddleware
$ app
Since 1.4.14
defaultCsrfSetCookieMiddleware :: HandlerFor site res -> HandlerFor site res Source #
Calls csrfSetCookieMiddleware
with the defaultCsrfCookieName
.
The cookie's path is set to /
, making it valid for your whole website.
Since 1.4.14
csrfSetCookieMiddleware :: HandlerFor site res -> SetCookie -> HandlerFor site res Source #
Takes a SetCookie
and overrides its value with a CSRF token, then sets the cookie. See setCsrfCookieWithCookie
.
For details, see the "AJAX CSRF protection" section of Yesod.Core.Handler.
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
defaultCsrfCheckMiddleware :: Yesod site => HandlerFor site res -> HandlerFor site res Source #
Calls csrfCheckMiddleware
with isWriteRequest
, defaultCsrfHeaderName
, and defaultCsrfParamName
as parameters.
Since 1.4.14
:: HandlerFor site res | |
-> HandlerFor site Bool | Whether or not to perform the CSRF check. |
-> CI ByteString | The header name to lookup the CSRF token from. |
-> Text | The POST parameter name to lookup the CSRF token from. |
-> HandlerFor site res |
Looks up the CSRF token from the request headers or POST parameters. If the value doesn't match the token stored in the session,
this function throws a PermissionDenied
error.
For details, see the "AJAX CSRF protection" section of Yesod.Core.Handler.
Since 1.4.14
JS loaders
data ScriptLoadPosition master Source #
type BottomOfHeadAsync master Source #
Generalizing type classes
class (MonadResource m, MonadLogger m) => MonadHandler m where Source #
type HandlerSite m Source #
type SubHandlerSite m Source #
liftHandler :: HandlerFor (HandlerSite m) a -> m a Source #
liftSubHandler :: SubHandlerFor (SubHandlerSite m) (HandlerSite m) a -> m a Source #
Instances
class MonadHandler m => MonadWidget m where Source #
liftWidget :: WidgetFor (HandlerSite m) a -> m a Source #
Instances
Approot
guessApproot :: Approot site Source #
Guess the approot based on request headers. For more information, see Network.Wai.Middleware.Approot
In the case of headers being unavailable, it falls back to ApprootRelative
Since 1.4.16
guessApprootOr :: Approot site -> Approot site Source #
Guess the approot based on request headers, with fall back to the
specified AppRoot
.
Since 1.4.16
getApprootText :: Approot site -> site -> Request -> Text Source #
Get the textual application root from an Approot
value.
Since 1.4.17
Misc
runFakeHandler :: (Yesod site, MonadIO m) => SessionMap -> (site -> Logger) -> site -> HandlerT site IO a -> m (Either ErrorResponse a) Source #
Deprecated: import runFakeHandler from Yesod.Core.Unsafe
LiteApp
LiteApp | |
|
Instances
type LiteHandler = HandlerFor LiteApp Source #
type LiteWidget = WidgetFor LiteApp Source #
dispatchTo :: ToTypedContent a => LiteHandler a -> Writer LiteApp () Source #
withDynamicMulti :: PathMultiPiece ps => (ps -> Writer LiteApp ()) -> Writer LiteApp () Source #
Low-level
yesodRunner :: (ToTypedContent res, Yesod site) => HandlerFor site res -> YesodRunnerEnv site -> Maybe (Route site) -> Application Source #
Re-exports
module Yesod.Core.Content
module Yesod.Core.Dispatch
module Yesod.Core.Handler
module Yesod.Core.Widget
module Yesod.Core.Json
module Text.Shakespeare.I18N
formatRFC1123 :: UTCTime -> Text Source #
Format as per RFC 1123.
formatRFC822 :: UTCTime -> Text Source #
Format as per RFC 822.
preEscapedToMarkup :: ToMarkup a => a -> Markup #
Convert a value to Markup without escaping
class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a monad transformation:
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
class MonadIO m => MonadUnliftIO (m :: Type -> Type) where #
Monads which allow their actions to be run in IO
.
While MonadIO
allows an IO
action to be lifted into another
monad, this class captures the opposite concept: allowing you to
capture the monadic context. Note that, in order to meet the laws
given below, the intuition is that a monad must have no monadic
state, but may have monadic context. This essentially limits
MonadUnliftIO
to ReaderT
and IdentityT
transformers on top of
IO
.
Laws. For any value u
returned by askUnliftIO
, it must meet the
monad transformer laws as reformulated for MonadUnliftIO
:
unliftIO u . return = return
unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f
Instances of MonadUnliftIO
must also satisfy the idempotency law:
askUnliftIO >>= \u -> (liftIO . unliftIO u) m = m
This law showcases two properties. First, askUnliftIO
doesn't change
the monadic context, and second, liftIO . unliftIO u
is equivalent to
id
IF called in the same monadic context as askUnliftIO
.
Since: unliftio-core-0.1.0.0
withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b #
Convenience function for capturing the monadic context and running an IO
action with a runner function. The runner function is used to run a monadic
action m
in IO
.
Since: unliftio-core-0.1.0.0
Instances
class MonadIO m => MonadResource (m :: Type -> Type) where #
A Monad
which allows for safe resource allocation. In theory, any monad
transformer stack which includes a ResourceT
can be an instance of
MonadResource
.
Note: runResourceT
has a requirement for a MonadUnliftIO m
monad,
which allows control operations to be lifted. A MonadResource
does not
have this requirement. This means that transformers such as ContT
can be
an instance of MonadResource
. However, the ContT
wrapper will need to be
unwrapped before calling runResourceT
.
Since 0.3.0
liftResourceT :: ResourceT IO a -> m a #
Lift a ResourceT IO
action into the current Monad
.
Since 0.4.0
Instances
class Monad m => MonadLogger (m :: Type -> Type) #
A Monad
which has the ability to log messages in some manner.
Instances
Commonly referenced functions/datatypes
type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #
The WAI application.
Note that, since WAI 3.0, this type is structured in continuation passing
style to allow for proper safe resource handling. This was handled in the
past via other means (e.g., ResourceT
). As a demonstration:
app :: Application app req respond = bracket_ (putStrLn "Allocating scarce resource") (putStrLn "Cleaning up") (respond $ responseLBS status200 [] "Hello World")
Utilities
showIntegral :: Integral a => a -> String Source #
Shakespeare
Hamlet
hamlet :: QuasiQuoter #
Hamlet quasi-quoter. May only be used to generate expressions.
Generated expression have type
, for some HtmlUrl
urlurl
.
data MyRoute = Home render ::Render
MyRoute render Home _ = "/home" >>>putStrLn
(renderHtml
([hamlet
|<a href=@{Home}>Home|] render)) <a href="/home">Home</a>
shamlet :: QuasiQuoter #
"Simple Hamlet" quasi-quoter. May only be used to generate expressions.
Generated expressions have type Html
.
>>>putStrLn
(renderHtml
[shamlet
|<div>Hello, world!|]) <div>Hello, world!</div>
xhamlet :: QuasiQuoter #
Like hamlet
, but produces XHTML.
type HtmlUrl url = Render url -> Html #
A function generating an Html
given a URL-rendering function.
Julius
julius :: QuasiQuoter #
type JavascriptUrl url = (url -> [(Text, Text)] -> Text) -> Javascript #
Return type of template-reading functions.
renderJavascriptUrl :: (url -> [(Text, Text)] -> Text) -> JavascriptUrl url -> Text #
render with route interpolation. If using this module standalone, apart from type-safe routes, a dummy renderer can be used:
renderJavascriptUrl (\_ _ -> undefined) javascriptUrl
When using Yesod, a renderer is generated for you, which can be accessed
within the GHandler monad: getUrlRenderParams
.
Cassius/Lucius
cassius :: QuasiQuoter #
lucius :: QuasiQuoter #
>>>
renderCss ([lucius|foo{bar:baz}|] undefined)
"foo{bar:baz}"