Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- type SessionMap = Map Text ByteString
- type SaveSession = SessionMap -> IO [Header]
- newtype SessionBackend = SessionBackend {
- sbLoadSession :: Request -> IO (SessionMap, SaveSession)
- data SessionCookie = SessionCookie !(Either UTCTime ByteString) !ByteString !SessionMap
- data ClientSessionDateCache = ClientSessionDateCache {}
- data YesodRequest = YesodRequest {
- reqGetParams :: ![(Text, Text)]
- reqCookies :: ![(Text, Text)]
- reqWaiRequest :: !Request
- reqLangs :: ![Text]
- reqToken :: !(Maybe Text)
- reqSession :: !SessionMap
- reqAccept :: ![ContentType]
- data YesodResponse
- = YRWai !Response
- | YRWaiApp !Application
- | YRPlain !Status ![Header] !ContentType !Content !SessionMap
- type RequestBodyContents = ([(Text, Text)], [(Text, FileInfo)])
- data FileInfo = FileInfo {
- fileName :: !Text
- fileContentType :: !Text
- fileSourceRaw :: !(ConduitT () ByteString (ResourceT IO) ())
- fileMove :: !(FilePath -> IO ())
- data FileUpload
- = FileUploadMemory !(BackEnd ByteString)
- | FileUploadDisk !(InternalState -> BackEnd FilePath)
- | FileUploadSource !(BackEnd (ConduitT () ByteString (ResourceT IO) ()))
- data Approot master
- = ApprootRelative
- | ApprootStatic !Text
- | ApprootMaster !(master -> Text)
- | ApprootRequest !(master -> Request -> Text)
- type ResolvedApproot = Text
- data AuthResult
- data ScriptLoadPosition master
- = BottomOfBody
- | BottomOfHeadBlocking
- | BottomOfHeadAsync !(BottomOfHeadAsync master)
- type BottomOfHeadAsync master = [Text] -> Maybe (HtmlUrl (Route master)) -> HtmlUrl (Route master)
- type Texts = [Text]
- newtype WaiSubsite = WaiSubsite {}
- newtype WaiSubsiteWithAuth = WaiSubsiteWithAuth {}
- data RunHandlerEnv child site = RunHandlerEnv {
- rheRender :: !(Route site -> [(Text, Text)] -> Text)
- rheRoute :: !(Maybe (Route child))
- rheRouteToMaster :: !(Route child -> Route site)
- rheSite :: !site
- rheChild :: !child
- rheUpload :: !(RequestBodyLength -> FileUpload)
- rheLog :: !(Loc -> LogSource -> LogLevel -> LogStr -> IO ())
- rheOnError :: !(ErrorResponse -> YesodApp)
- rheMaxExpires :: !Text
- data HandlerData child site = HandlerData {
- handlerRequest :: !YesodRequest
- handlerEnv :: !(RunHandlerEnv child site)
- handlerState :: !(IORef GHState)
- handlerResource :: !InternalState
- data YesodRunnerEnv site = YesodRunnerEnv {
- yreLogger :: !Logger
- yreSite :: !site
- yreSessionBackend :: !(Maybe SessionBackend)
- yreGen :: !(IO Int)
- yreGetMaxExpires :: !(IO Text)
- data YesodSubRunnerEnv sub parent = YesodSubRunnerEnv {
- ysreParentRunner :: !(ParentRunner parent)
- ysreGetSub :: !(parent -> sub)
- ysreToParentRoute :: !(Route sub -> Route parent)
- ysreParentEnv :: !(YesodRunnerEnv parent)
- type ParentRunner parent = HandlerFor parent TypedContent -> YesodRunnerEnv parent -> Maybe (Route parent) -> Application
- newtype HandlerFor site a = HandlerFor {
- unHandlerFor :: HandlerData site site -> IO a
- data GHState = GHState {
- ghsSession :: !SessionMap
- ghsRBC :: !(Maybe RequestBodyContents)
- ghsIdent :: !Int
- ghsCache :: !TypeMap
- ghsCacheBy :: !KeyedTypeMap
- ghsHeaders :: !(Endo [Header])
- type YesodApp = YesodRequest -> ResourceT IO YesodResponse
- newtype WidgetFor site a = WidgetFor {
- unWidgetFor :: WidgetData site -> IO a
- data WidgetData site = WidgetData {}
- tellWidget :: GWData (Route site) -> WidgetFor site ()
- type RY master = Route master -> [(Text, Text)] -> Text
- newtype CssBuilder = CssBuilder {}
- data PageContent url = PageContent {}
- data Content
- = ContentBuilder !Builder !(Maybe Int)
- | ContentSource !(ConduitT () (Flush Builder) (ResourceT IO) ())
- | ContentFile !FilePath !(Maybe FilePart)
- | ContentDontEvaluate !Content
- data TypedContent = TypedContent !ContentType !Content
- type RepHtml = Html
- newtype RepJson = RepJson Content
- newtype RepPlain = RepPlain Content
- newtype RepXml = RepXml Content
- type ContentType = ByteString
- newtype DontFullyEvaluate a = DontFullyEvaluate {
- unDontFullyEvaluate :: a
- data ErrorResponse
- data Header
- data Location url
- newtype UniqueList x = UniqueList ([x] -> [x])
- data Script url = Script {
- scriptLocation :: !(Location url)
- scriptAttributes :: ![(Text, Text)]
- data Stylesheet url = Stylesheet {
- styleLocation :: !(Location url)
- styleAttributes :: ![(Text, Text)]
- newtype Title = Title {}
- newtype Head url = Head (HtmlUrl url)
- newtype Body url = Body (HtmlUrl url)
- type CssBuilderUrl a = (a -> [(Text, Text)] -> Text) -> Builder
- data GWData a = GWData {
- gwdBody :: !(Body a)
- gwdTitle :: !(Last Title)
- gwdScripts :: !(UniqueList (Script a))
- gwdStylesheets :: !(UniqueList (Stylesheet a))
- gwdCss :: !(Map (Maybe Text) (CssBuilderUrl a))
- gwdJavascript :: !(Maybe (JavascriptUrl a))
- gwdHead :: !(Head a)
- data HandlerContents
- = HCContent !Status !TypedContent
- | HCError !ErrorResponse
- | HCSendFile !ContentType !FilePath !(Maybe FilePart)
- | HCRedirect !Status !Text
- | HCCreated !Text
- | HCWai !Response
- | HCWaiApp !Application
- data Logger = Logger {}
- loggerPutStr :: Logger -> LogStr -> IO ()
- newtype SubHandlerFor sub master a = SubHandlerFor {
- unSubHandlerFor :: HandlerData sub master -> IO a
Documentation
type SessionMap = Map Text ByteString Source #
type SaveSession Source #
= SessionMap | The session contents after running the handler |
-> IO [Header] |
newtype SessionBackend Source #
SessionBackend | |
|
data SessionCookie Source #
Instances
Read SessionCookie Source # | |
Defined in Yesod.Core.Types readsPrec :: Int -> ReadS SessionCookie # readList :: ReadS [SessionCookie] # | |
Show SessionCookie Source # | |
Defined in Yesod.Core.Types showsPrec :: Int -> SessionCookie -> ShowS # show :: SessionCookie -> String # showList :: [SessionCookie] -> ShowS # | |
Serialize SessionCookie Source # | |
Defined in Yesod.Core.Types put :: Putter SessionCookie # get :: Get SessionCookie # |
data ClientSessionDateCache Source #
ClientSessionDateCache | |
|
Instances
Eq ClientSessionDateCache Source # | |
Defined in Yesod.Core.Types | |
Show ClientSessionDateCache Source # | |
Defined in Yesod.Core.Types showsPrec :: Int -> ClientSessionDateCache -> ShowS # show :: ClientSessionDateCache -> String # showList :: [ClientSessionDateCache] -> ShowS # |
data YesodRequest Source #
The parsed request information. This type augments the standard WAI
Request
with additional information.
YesodRequest | |
|
data YesodResponse Source #
An augmented WAI Response
. This can either be a standard Response
,
or a higher-level data structure which Yesod will turn into a Response
.
type RequestBodyContents = ([(Text, Text)], [(Text, FileInfo)]) Source #
A tuple containing both the POST parameters and submitted files.
FileInfo | |
|
data FileUpload Source #
FileUploadMemory !(BackEnd ByteString) | |
FileUploadDisk !(InternalState -> BackEnd FilePath) | |
FileUploadSource !(BackEnd (ConduitT () ByteString (ResourceT IO) ())) |
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) |
type ResolvedApproot = Text Source #
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 # |
data ScriptLoadPosition master Source #
type BottomOfHeadAsync master Source #
newtype WaiSubsite Source #
Wrap up a normal WAI application as a Yesod subsite. Ignore parent site's middleware and isAuthorized.
Instances
newtype WaiSubsiteWithAuth Source #
Like WaiSubsite
, but applies parent site's middleware and isAuthorized.
Since: yesod-core-1.4.34
Instances
data RunHandlerEnv child site Source #
RunHandlerEnv | |
|
data HandlerData child site Source #
HandlerData | |
|
Instances
MonadReader (HandlerData site site) (HandlerFor site) Source # | |
Defined in Yesod.Core.Types 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 # | |
MonadReader (HandlerData child master) (SubHandlerFor child master) Source # | |
Defined in Yesod.Core.Types 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 # |
data YesodRunnerEnv site Source #
YesodRunnerEnv | |
|
data YesodSubRunnerEnv sub parent Source #
YesodSubRunnerEnv | |
|
type ParentRunner parent = HandlerFor parent TypedContent -> YesodRunnerEnv parent -> Maybe (Route parent) -> Application Source #
newtype 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.
HandlerFor | |
|
Instances
GHState | |
|
type YesodApp = YesodRequest -> ResourceT IO YesodResponse 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 HandlerT
monad and template haskell code should hide it away.
newtype WidgetFor site a Source #
A generic widget, allowing specification of both the subsite and master
site datatypes. While this is simply a WriterT
, we define a newtype for
better error messages.
WidgetFor | |
|
Instances
data WidgetData site Source #
Instances
MonadReader (WidgetData site) (WidgetFor site) Source # | |
Defined in Yesod.Core.Types ask :: WidgetFor site (WidgetData site) # local :: (WidgetData site -> WidgetData site) -> WidgetFor site a -> WidgetFor site a # reader :: (WidgetData site -> a) -> WidgetFor site a # |
newtype CssBuilder Source #
Newtype wrapper allowing injection of arbitrary content into CSS.
Usage:
toWidget $ CssBuilder "p { color: red }"
Since: 1.1.3
Instances
data PageContent url Source #
Content for a web page. By providing this datatype, we can easily create generic site templates, which would have the type signature:
PageContent url -> HtmlUrl url
ContentBuilder !Builder !(Maybe Int) | The content and optional content length. |
ContentSource !(ConduitT () (Flush Builder) (ResourceT IO) ()) | |
ContentFile !FilePath !(Maybe FilePart) | |
ContentDontEvaluate !Content |
Instances
IsString Content Source # | |
Defined in Yesod.Core.Types fromString :: String -> Content # | |
ToContent Content Source # | |
ToTypedContent (ContentType, Content) Source # | |
Defined in Yesod.Core.Content toTypedContent :: (ContentType, Content) -> TypedContent Source # | |
ToContent (ContentType, Content) Source # | |
Defined in Yesod.Core.Content |
data TypedContent Source #
Instances
ToTypedContent TypedContent Source # | |
Defined in Yesod.Core.Content | |
ToContent TypedContent Source # | |
Defined in Yesod.Core.Content toContent :: TypedContent -> Content Source # |
Instances
ToTypedContent RepJson Source # | |
Defined in Yesod.Core.Content toTypedContent :: RepJson -> TypedContent Source # | |
HasContentType RepJson Source # | |
Defined in Yesod.Core.Content getContentType :: Monad m => m RepJson -> ContentType Source # | |
ToContent RepJson Source # | |
Instances
ToTypedContent RepPlain Source # | |
Defined in Yesod.Core.Content | |
HasContentType RepPlain Source # | |
Defined in Yesod.Core.Content getContentType :: Monad m => m RepPlain -> ContentType Source # | |
ToContent RepPlain Source # | |
Instances
ToTypedContent RepXml Source # | |
Defined in Yesod.Core.Content toTypedContent :: RepXml -> TypedContent Source # | |
HasContentType RepXml Source # | |
Defined in Yesod.Core.Content getContentType :: Monad m => m RepXml -> ContentType Source # | |
ToContent RepXml Source # | |
type ContentType = ByteString Source #
newtype DontFullyEvaluate a Source #
Prevents a response body from being fully evaluated before sending the request.
Since 1.1.0
Instances
ToTypedContent a => ToTypedContent (DontFullyEvaluate a) Source # | |
Defined in Yesod.Core.Content | |
HasContentType a => HasContentType (DontFullyEvaluate a) Source # | |
Defined in Yesod.Core.Content getContentType :: Monad m => m (DontFullyEvaluate a) -> ContentType Source # | |
ToContent a => ToContent (DontFullyEvaluate a) Source # | |
Defined in Yesod.Core.Content toContent :: DontFullyEvaluate a -> Content Source # |
data ErrorResponse Source #
Responses to indicate some form of an error occurred.
NotFound | |
InternalError !Text | |
InvalidArgs ![Text] | |
NotAuthenticated | |
PermissionDenied !Text | |
BadMethod !Method |
Instances
Headers to be added to a Result
.
AddCookie !SetCookie | |
DeleteCookie !ByteString !ByteString | name and path |
Header !(CI ByteString) !ByteString | key and value |
newtype UniqueList x Source #
A diff list that does not directly enforce uniqueness. When creating a widget Yesod will use nub to make it unique.
UniqueList ([x] -> [x]) |
Instances
Semigroup (UniqueList x) Source # | |
Defined in Yesod.Core.Types (<>) :: UniqueList x -> UniqueList x -> UniqueList x # sconcat :: NonEmpty (UniqueList x) -> UniqueList x # stimes :: Integral b => b -> UniqueList x -> UniqueList x # | |
Monoid (UniqueList x) Source # | |
Defined in Yesod.Core.Types mempty :: UniqueList x # mappend :: UniqueList x -> UniqueList x -> UniqueList x # mconcat :: [UniqueList x] -> UniqueList x # |
Script | |
|
data Stylesheet url Source #
Stylesheet | |
|
Instances
Eq url => Eq (Stylesheet url) Source # | |
Defined in Yesod.Core.Types (==) :: Stylesheet url -> Stylesheet url -> Bool # (/=) :: Stylesheet url -> Stylesheet url -> Bool # | |
Show url => Show (Stylesheet url) Source # | |
Defined in Yesod.Core.Types showsPrec :: Int -> Stylesheet url -> ShowS # show :: Stylesheet url -> String # showList :: [Stylesheet url] -> ShowS # |
GWData | |
|
data HandlerContents Source #
HCContent !Status !TypedContent | |
HCError !ErrorResponse | |
HCSendFile !ContentType !FilePath !(Maybe FilePart) | |
HCRedirect !Status !Text | |
HCCreated !Text | |
HCWai !Response | |
HCWaiApp !Application |
Instances
Show HandlerContents Source # | |
Defined in Yesod.Core.Types showsPrec :: Int -> HandlerContents -> ShowS # show :: HandlerContents -> String # showList :: [HandlerContents] -> ShowS # | |
Exception HandlerContents Source # | |
Defined in Yesod.Core.Types |
newtype SubHandlerFor sub master a Source #
A handler monad for subsite
Since: yesod-core-1.6.0
SubHandlerFor | |
|