Safe Haskell | None |
---|
- class RenderRoute site => Yesod site where
- approot :: Approot site
- errorHandler :: ErrorResponse -> HandlerT site IO TypedContent
- defaultLayout :: WidgetT site IO () -> HandlerT site IO Html
- urlRenderOverride :: site -> Route site -> Maybe Builder
- isAuthorized :: Route site -> Bool -> HandlerT site IO AuthResult
- isWriteRequest :: Route site -> HandlerT site IO Bool
- authRoute :: site -> Maybe (Route site)
- cleanPath :: site -> [Text] -> Either [Text] [Text]
- joinPath :: site -> Text -> [Text] -> [(Text, Text)] -> Builder
- addStaticContent :: Text -> Text -> ByteString -> HandlerT site IO (Maybe (Either Text (Route site, [(Text, Text)])))
- maximumContentLength :: site -> Maybe (Route site) -> Maybe Word64
- makeLogger :: site -> IO Logger
- messageLoggerSource :: site -> Logger -> Loc -> LogSource -> LogLevel -> LogStr -> IO ()
- jsLoader :: site -> ScriptLoadPosition site
- makeSessionBackend :: site -> IO (Maybe SessionBackend)
- fileUpload :: site -> RequestBodyLength -> FileUpload
- shouldLog :: site -> LogSource -> LogLevel -> Bool
- shouldLogIO :: site -> LogSource -> LogLevel -> IO Bool
- yesodMiddleware :: ToTypedContent res => HandlerT site IO res -> HandlerT site IO res
- class Yesod site => YesodDispatch site where
- yesodDispatch :: YesodRunnerEnv site -> Application
- class YesodSubDispatch sub m where
- yesodSubDispatch :: YesodSubRunnerEnv sub (HandlerSite m) m -> 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
- breadcrumbs :: YesodBreadcrumbs site => HandlerT site IO (Text, [(Route site, Text)])
- data Approot master
- = ApprootRelative
- | ApprootStatic !Text
- | ApprootMaster !(master -> Text)
- | ApprootRequest !(master -> Request -> Text)
- data FileUpload
- = FileUploadMemory !(BackEnd ByteString)
- | FileUploadDisk !(BackEnd FilePath)
- | FileUploadSource !(BackEnd (Source (ResourceT IO) ByteString))
- data ErrorResponse
- = NotFound
- | InternalError Text
- | InvalidArgs [Text]
- | NotAuthenticated
- | PermissionDenied Text
- | BadMethod Method
- maybeAuthorized :: Yesod site => Route site -> Bool -> HandlerT site IO (Maybe (Route site))
- widgetToPageContent :: (Eq (Route site), Yesod site) => WidgetT site IO () -> HandlerT site IO (PageContent (Route site))
- defaultErrorHandler :: Yesod site => ErrorResponse -> HandlerT site IO TypedContent
- data AuthResult
- unauthorizedI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => msg -> m AuthResult
- data LogLevel
- = LevelDebug
- | LevelInfo
- | LevelWarn
- | LevelError
- | LevelOther Text
- 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
- clientSessionBackend :: Key -> IO ClientSessionDateCache -> SessionBackend
- clientSessionDateCacher :: NominalDiffTime -> IO (IO ClientSessionDateCache, IO ())
- loadClientSession :: Key -> IO ClientSessionDateCache -> ByteString -> Request -> IO (SessionMap, SaveSession)
- data Header
- data ScriptLoadPosition master
- = BottomOfBody
- | BottomOfHeadBlocking
- | BottomOfHeadAsync (BottomOfHeadAsync master)
- type BottomOfHeadAsync master = [Text] -> Maybe (HtmlUrl (Route master)) -> HtmlUrl (Route master)
- class MonadResource m => MonadHandler m where
- type HandlerSite m
- liftHandlerT :: HandlerT (HandlerSite m) IO a -> m a
- class MonadHandler m => MonadWidget m where
- liftWidgetT :: WidgetT (HandlerSite m) IO a -> m a
- getRouteToParent :: Monad m => HandlerT child (HandlerT parent m) (Route child -> Route parent)
- defaultLayoutSub :: Yesod parent => WidgetT child IO () -> HandlerT child (HandlerT parent IO) Html
- 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 = HandlerT LiteApp IO
- type LiteWidget = WidgetT LiteApp IO
- 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) => HandlerT site IO 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
- putTime :: UTCTime -> Put
- getTime :: Get UTCTime
- formatW3 :: UTCTime -> Text
- formatRFC1123 :: UTCTime -> Text
- formatRFC822 :: UTCTime -> Text
- module Text.Blaze.Html
- class MonadTrans t where
- class Monad m => MonadIO m where
- class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where
- liftBase :: b α -> m α
- class MonadBase b m => MonadBaseControl b m | m -> b
- class (MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative m) => MonadResource m where
- liftResourceT :: ResourceT IO a -> m a
- class Monad m => MonadLogger m
- type Application = Request -> IO Response
- 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 whereSource
Define settings for a Yesod applications. All methods have intelligent defaults, and therefore no implementation is required.
An absolute URL to the root of the application. Do not include trailing slash.
Default value: ApprootRelative
. This is valid under the following
conditions:
- Your application is served from the root of the domain.
- You do not use any features that require absolute URLs, such as Atom feeds and XML sitemaps.
If this is not true, you should override with a different implementation.
errorHandler :: ErrorResponse -> HandlerT site IO TypedContentSource
Output error response pages.
Default value: defaultErrorHandler
.
defaultLayout :: WidgetT site IO () -> HandlerT site IO HtmlSource
Applies some form of layout to the contents of a page.
urlRenderOverride :: site -> Route site -> Maybe BuilderSource
Override the rendering function for a particular URL. One use case for this is to offload static hosting to a different domain name to avoid sending cookies.
:: Route site | |
-> Bool | is this a write request? |
-> HandlerT site IO 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 -> HandlerT site IO BoolSource
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 |
-> HandlerT site IO (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 Word64Source
Maximum allowed length of the request body, in bytes.
If Nothing
, no maximum is applied.
Default: 2 megabytes.
makeLogger :: site -> IO LoggerSource
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: Sends to stdout and automatically flushes on each write.
Send a message to the Logger
provided by getLogger
.
Default implementation: checks if the message should be logged using
shouldLog
and, if so, formats using formatLogMessage
.
jsLoader :: site -> ScriptLoadPosition siteSource
Where to Load sripts from. We recommend the default value,
BottomOfBody
. Alternatively use the built in async yepnope loader:
BottomOfHeadAsync $ loadJsYepnope $ Right $ StaticR js_modernizr_js
Or write your own async js loader.
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 -> FileUploadSource
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.
shouldLog :: site -> LogSource -> LogLevel -> BoolSource
Should we log the given log source/level combination.
Default: Logs everything at or above logLevel
shouldLogIO :: site -> LogSource -> LogLevel -> IO BoolSource
Should we log the given log source/level combination.
Note that this is almost identical to shouldLog
, except the result
lives in IO
. This allows you to dynamically alter the logging level of
your application by having this result depend on, e.g., an IORef
.
The default implementation simply uses shouldLog
. Future versions of
Yesod will remove shouldLog
and use this method exclusively.
Since 1.2.4
yesodMiddleware :: ToTypedContent res => HandlerT site IO res -> HandlerT site IO resSource
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
class Yesod site => YesodDispatch site whereSource
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 -> ApplicationSource
class YesodSubDispatch sub m whereSource
yesodSubDispatch :: YesodSubRunnerEnv sub (HandlerSite m) m -> ApplicationSource
YesodSubDispatch WaiSubsite master |
class Eq (Route a) => RenderRoute a where
data Route a1
The type-safe URLs associated with a site argument.
renderRoute :: Route a -> ([Text], [(Text, Text)])
class RenderRoute a => ParseRoute a where
class RenderRoute a => RouteAttrs a where
routeAttrs :: Route a -> Set Text
Breadcrumbs
class YesodBreadcrumbs site whereSource
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).
breadcrumbs :: YesodBreadcrumbs site => HandlerT site IO (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
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.
Utitlities
:: Yesod site | |
=> Route site | |
-> Bool | is this a write request? |
-> HandlerT site IO (Maybe (Route site)) |
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 :: (Eq (Route site), Yesod site) => WidgetT site IO () -> HandlerT site IO (PageContent (Route site))Source
Convert a widget to a PageContent
.
Defaults
defaultErrorHandler :: Yesod site => ErrorResponse -> HandlerT site IO TypedContentSource
The default error handler for errorHandler
.
Data types
data AuthResult Source
unauthorizedI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => msg -> m AuthResultSource
Return an Unauthorized
value, with the given i18n message.
Logging
data LogLevel
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 -> SessionBackendSource
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 = fmap (customizeSessionCookie addDomain) ...
where
addDomain cookie = cookie { setCookieDomain
= Just ".example.com" }
Default: Do not customize anything (id
).
defaultClientSessionBackendSource
:: Int | minutes |
-> FilePath | key file |
-> IO SessionBackend |
:: Key | The encryption key |
-> IO ClientSessionDateCache | |
-> SessionBackend |
:: NominalDiffTime | Inactive session valitity. |
-> IO (IO ClientSessionDateCache, IO ()) |
:: Key | |
-> IO ClientSessionDateCache | |
-> ByteString | session name |
-> Request | |
-> IO (SessionMap, SaveSession) |
Headers to be added to a Result
.
JS loaders
data ScriptLoadPosition master Source
type BottomOfHeadAsync masterSource
Subsites
class MonadResource m => MonadHandler m whereSource
type HandlerSite m Source
liftHandlerT :: HandlerT (HandlerSite m) IO a -> m aSource
MonadHandler m => MonadHandler (ExceptionT m) | |
MonadHandler m => MonadHandler (ListT m) | |
MonadHandler m => MonadHandler (MaybeT m) | |
MonadHandler m => MonadHandler (IdentityT m) | |
(Error e, MonadHandler m) => MonadHandler (ErrorT e m) | |
MonadHandler m => MonadHandler (ReaderT r m) | |
MonadHandler m => MonadHandler (StateT s m) | |
MonadHandler m => MonadHandler (StateT s m) | |
(Monoid w, MonadHandler m) => MonadHandler (WriterT w m) | |
(Monoid w, MonadHandler m) => MonadHandler (WriterT w m) | |
MonadResourceBase m => MonadHandler (WidgetT site m) | |
MonadResourceBase m => MonadHandler (HandlerT site m) | |
MonadHandler m => MonadHandler (ConduitM i o m) | |
(Monoid w, MonadHandler m) => MonadHandler (RWST r w s m) | |
(Monoid w, MonadHandler m) => MonadHandler (RWST r w s m) | |
MonadHandler m => MonadHandler (Pipe l i o u m) |
class MonadHandler m => MonadWidget m whereSource
liftWidgetT :: WidgetT (HandlerSite m) IO a -> m aSource
MonadWidget m => MonadWidget (ExceptionT m) | |
MonadWidget m => MonadWidget (ListT m) | |
MonadWidget m => MonadWidget (MaybeT m) | |
MonadWidget m => MonadWidget (IdentityT m) | |
(Error e, MonadWidget m) => MonadWidget (ErrorT e m) | |
MonadWidget m => MonadWidget (ReaderT r m) | |
MonadWidget m => MonadWidget (StateT s m) | |
MonadWidget m => MonadWidget (StateT s m) | |
(Monoid w, MonadWidget m) => MonadWidget (WriterT w m) | |
(Monoid w, MonadWidget m) => MonadWidget (WriterT w m) | |
MonadResourceBase m => MonadWidget (WidgetT site m) | |
MonadWidget m => MonadWidget (ConduitM i o m) | |
(Monoid w, MonadWidget m) => MonadWidget (RWST r w s m) | |
(Monoid w, MonadWidget m) => MonadWidget (RWST r w s m) | |
MonadWidget m => MonadWidget (Pipe l i o u m) |
getRouteToParent :: Monad m => HandlerT child (HandlerT parent m) (Route child -> Route parent)Source
defaultLayoutSub :: Yesod parent => WidgetT child IO () -> HandlerT child (HandlerT parent IO) HtmlSource
Misc
runFakeHandler :: (Yesod site, MonadIO m) => SessionMap -> (site -> Logger) -> site -> HandlerT site IO a -> m (Either ErrorResponse a)Source
Warning: Usually you should *not* use runFakeHandler unless you really understand how it works and why you need it.
Run a HandlerT
completely outside of Yesod. This
function comes with many caveats and you shouldn't use it
unless you fully understand what it's doing and how it works.
As of now, there's only one reason to use this function at
all: in order to run unit tests of functions inside HandlerT
but that aren't easily testable with a full HTTP request.
Even so, it's better to use wai-test
or yesod-test
instead
of using this function.
This function will create a fake HTTP request (both wai
's
Request
and yesod
's Request
) and feed it to the
HandlerT
. The only useful information the HandlerT
may
get from the request is the session map, which you must supply
as argument to runFakeHandler
. All other fields contain
fake information, which means that they can be accessed but
won't have any useful information. The response of the
HandlerT
is completely ignored, including changes to the
session, cookies or headers. We only return you the
HandlerT
's return value.
LiteApp
LiteApp | |
|
type LiteHandler = HandlerT LiteApp IOSource
type LiteWidget = WidgetT LiteApp IOSource
dispatchTo :: ToTypedContent a => LiteHandler a -> Writer LiteApp ()Source
withDynamicMulti :: PathMultiPiece ps => (ps -> Writer LiteApp ()) -> Writer LiteApp ()Source
Low-level
yesodRunner :: (ToTypedContent res, Yesod site) => HandlerT site IO res -> YesodRunnerEnv site -> Maybe (Route site) -> ApplicationSource
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 -> TextSource
Format as per RFC 1123.
formatRFC822 :: UTCTime -> TextSource
Format as per RFC 822.
module Text.Blaze.Html
class MonadTrans t where
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a transformer of monads:
MonadTrans ExceptionT | |
MonadTrans ResourceT | |
MonadTrans NoLoggingT | |
MonadTrans LoggingT | |
MonadTrans ListT | |
MonadTrans MaybeT | |
MonadTrans IdentityT | |
MonadTrans (ContT r) | |
Error e => MonadTrans (ErrorT e) | |
MonadTrans (ReaderT r) | |
MonadTrans (StateT s) | |
MonadTrans (StateT s) | |
Monoid w => MonadTrans (WriterT w) | |
Monoid w => MonadTrans (WriterT w) | |
MonadTrans (WidgetT site) | |
MonadTrans (HandlerT site) | |
MonadTrans (ConduitM i o) | |
Monoid w => MonadTrans (RWST r w s) | |
Monoid w => MonadTrans (RWST r w s) | |
MonadTrans (Pipe l i o u) |
class Monad m => MonadIO m 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:
MonadIO IO | |
MonadIO m => MonadIO (ExceptionT m) | |
MonadIO m => MonadIO (ResourceT m) | |
MonadIO m => MonadIO (NoLoggingT m) | |
MonadIO m => MonadIO (LoggingT m) | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (MaybeT m) | |
MonadIO m => MonadIO (IdentityT m) | |
MonadIO m => MonadIO (ContT r m) | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
MonadIO m => MonadIO (ReaderT r m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
MonadIO m => MonadIO (WidgetT site m) | |
MonadIO m => MonadIO (HandlerT site m) | |
MonadIO m => MonadIO (ConduitM i o m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
MonadIO m => MonadIO (Pipe l i o u m) |
class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where
liftBase :: b α -> m α
Lift a computation from the base monad
class MonadBase b m => MonadBaseControl b m | m -> b
class (MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative m) => MonadResource m where
A Monad
which allows for safe resource allocation. In theory, any monad
transformer stack included a ResourceT
can be an instance of
MonadResource
.
Note: runResourceT
has a requirement for a MonadBaseControl IO 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
class Monad m => MonadLogger m
MonadLogger m => MonadLogger (ResourceT m) | |
MonadIO m => MonadLogger (NoLoggingT m) | |
MonadIO m => MonadLogger (LoggingT m) | |
MonadLogger m => MonadLogger (ListT m) | |
MonadLogger m => MonadLogger (MaybeT m) | |
MonadLogger m => MonadLogger (IdentityT m) | |
MonadLogger m => MonadLogger (ContT r m) | |
(MonadLogger m, Error e) => MonadLogger (ErrorT e m) | |
MonadLogger m => MonadLogger (ReaderT r m) | |
MonadLogger m => MonadLogger (StateT s m) | |
MonadLogger m => MonadLogger (StateT s m) | |
(MonadLogger m, Monoid w) => MonadLogger (WriterT w m) | |
(MonadLogger m, Monoid w) => MonadLogger (WriterT w m) | |
MonadIO m => MonadLogger (WidgetT site m) | |
MonadIO m => MonadLogger (HandlerT site m) | |
MonadLogger m => MonadLogger (ConduitM i o m) | |
(MonadLogger m, Monoid w) => MonadLogger (RWST r w s m) | |
(MonadLogger m, Monoid w) => MonadLogger (RWST r w s m) | |
MonadLogger m => MonadLogger (Pipe l i o u m) |
Commonly referenced functions/datatypes
type Application = Request -> IO Response
The WAI application.
Utilities
showIntegral :: Integral a => a -> StringSource
readIntegral :: Num a => String -> Maybe aSource
Shakespeare
Hamlet
Julius
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
>>>
renderCss ([lucius|foo{bar:baz}|] undefined)
"foo{bar:baz}"