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

Safe HaskellNone
LanguageHaskell98

Yesod.Core.Types

Synopsis

Documentation

type SaveSession Source

Arguments

 = SessionMap

The session contents after running the handler

-> IO [Header] 

newtype SessionBackend Source

Constructors

SessionBackend 

Fields

sbLoadSession :: Request -> IO (SessionMap, SaveSession)

Return the session data and a function to save the session

data YesodRequest Source

The parsed request information. This type augments the standard WAI Request with additional information.

Constructors

YesodRequest 

Fields

reqGetParams :: ![(Text, Text)]

Same as queryString, but decoded to Text.

reqCookies :: ![(Text, Text)]
 
reqWaiRequest :: !Request
 
reqLangs :: ![Text]

Languages which the client supports. This is an ordered list by preference.

reqToken :: !(Maybe Text)

A random, session-specific token used to prevent CSRF attacks.

reqSession :: !SessionMap

Initial session sent from the client.

Since 1.2.0

reqAccept :: ![ContentType]

An ordered list of the accepted content types.

Since 1.2.0

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.

Constructors

YRWai !Response 
YRWaiApp !Application 
YRPlain !Status ![Header] !ContentType !Content !SessionMap 

type RequestBodyContents = ([(Text, Text)], [(Text, FileInfo)]) Source

A tuple containing both the POST parameters and submitted files.

data FileInfo Source

Constructors

FileInfo 

Fields

fileName :: !Text
 
fileContentType :: !Text
 
fileSourceRaw :: !(Source (ResourceT IO) ByteString)
 
fileMove :: !(FilePath -> IO ())
 

data FileUpload Source

Constructors

FileUploadMemory !(BackEnd ByteString) 
FileUploadDisk !(InternalState -> BackEnd FilePath) 
FileUploadSource !(BackEnd (Source (ResourceT IO) ByteString)) 

data Approot master Source

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.

Constructors

ApprootRelative

No application root.

ApprootStatic !Text 
ApprootMaster !(master -> Text) 
ApprootRequest !(master -> Request -> Text) 

type BottomOfHeadAsync master Source

Arguments

 = [Text]

urls to load asynchronously

-> Maybe (HtmlUrl (Route master))

widget of js to run on async completion

-> HtmlUrl (Route master)

widget to insert at the bottom of head

newtype Cache Source

Constructors

Cache (Map TypeRep Dynamic) 

Instances

type Texts = [Text] Source

newtype WaiSubsite Source

Wrap up a normal WAI application as a Yesod subsite.

Constructors

WaiSubsite 

data RunHandlerEnv site Source

Constructors

RunHandlerEnv 

Fields

rheRender :: !(Route site -> [(Text, Text)] -> Text)
 
rheRoute :: !(Maybe (Route site))
 
rheSite :: !site
 
rheUpload :: !(RequestBodyLength -> FileUpload)
 
rheLog :: !(Loc -> LogSource -> LogLevel -> LogStr -> IO ())
 
rheOnError :: !(ErrorResponse -> YesodApp)

How to respond when an error is thrown internally.

Since 1.2.0

data HandlerData site parentRoute Source

Constructors

HandlerData 

Fields

handlerRequest :: !YesodRequest
 
handlerEnv :: !(RunHandlerEnv site)
 
handlerState :: !(IORef GHState)
 
handlerToParent :: !(Route site -> parentRoute)
 
handlerResource :: !InternalState
 

data YesodSubRunnerEnv sub parent parentMonad Source

Constructors

YesodSubRunnerEnv 

Fields

ysreParentRunner :: !(ParentRunner parent parentMonad)
 
ysreGetSub :: !(parent -> sub)
 
ysreToParentRoute :: !(Route sub -> Route parent)
 
ysreParentEnv :: !(YesodRunnerEnv parent)
 

type ParentRunner parent m = m TypedContent -> YesodRunnerEnv parent -> Maybe (Route parent) -> Application Source

newtype HandlerT site m a Source

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

Constructors

HandlerT 

Fields

unHandlerT :: HandlerData site (MonadRoute m) -> m a
 

Instances

MonadBase b m => MonadBase b (HandlerT site m) 
Monad m => MonadReader site (HandlerT site m) 
MonadBaseControl b m => MonadBaseControl b (HandlerT site m)

Note: although we provide a MonadBaseControl instance, lifted-base's fork function is incompatible with the underlying ResourceT system. Instead, if you must fork a separate thread, you should use resourceForkIO.

Using fork usually leads to an exception that says "Control.Monad.Trans.Resource.register': The mutable state is being accessed after cleanup. Please contact the maintainers."

MonadTrans (HandlerT site) 
Monad m => Monad (HandlerT site m) 
Monad m => Functor (HandlerT site m) 
Monad m => Applicative (HandlerT site m) 
MonadIO m => MonadIO (HandlerT site m) 
MonadThrow m => MonadThrow (HandlerT site m) 
MonadMask m => MonadMask (HandlerT site m) 
MonadCatch m => MonadCatch (HandlerT site m) 
(MonadIO m, MonadBase IO m, MonadThrow m) => MonadResource (HandlerT site m) 
MonadIO m => MonadLogger (HandlerT site m) 
MonadResourceBase m => MonadHandler (HandlerT site m) 
data StM (HandlerT site m) = StH (StM m a) 
type MonadRoute (HandlerT site m) = Route site 
type HandlerSite (HandlerT site m) = site 

type family MonadRoute m Source

Instances

type MonadRoute IO = () 
type MonadRoute (HandlerT site m) = Route site 

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 WidgetT site m 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.

Constructors

WidgetT 

Fields

unWidgetT :: HandlerData site (MonadRoute m) -> m (a, GWData (Route site))
 

Instances

MonadBase b m => MonadBase b (WidgetT site m) 
Monad m => MonadReader site (WidgetT site m) 
MonadBaseControl b m => MonadBaseControl b (WidgetT site m) 
((~) * site' site, (~) (* -> *) IO m, (~) * a ()) => ToWidget site' (WidgetT site m a) 
MonadTrans (WidgetT site) 
Monad m => Monad (WidgetT site m) 
Monad m => Functor (WidgetT site m) 
Monad m => Applicative (WidgetT site m) 
MonadIO m => MonadIO (WidgetT site m) 
MonadThrow m => MonadThrow (WidgetT site m) 
MonadMask m => MonadMask (WidgetT site m) 
MonadCatch m => MonadCatch (WidgetT site m) 
(Applicative m, MonadIO m, MonadBase IO m, MonadThrow m) => MonadResource (WidgetT site m) 
MonadIO m => MonadLogger (WidgetT site m) 
MonadResourceBase m => MonadWidget (WidgetT site m) 
MonadResourceBase m => MonadHandler (WidgetT site m) 
((~) * a (), Monad m) => Monoid (WidgetT site m a) 
data StM (WidgetT site m) = StW (StM m (a, GWData (Route site))) 
type HandlerSite (WidgetT site m) = site 

type RY master = Route master -> [(Text, Text)] -> Text Source

newtype CssBuilder Source

Newtype wrapper allowing injection of arbitrary content into CSS.

Usage:

toWidget $ CssBuilder "p { color: red }"

Since: 1.1.3

Constructors

CssBuilder 

Fields

unCssBuilder :: Builder
 

Instances

ToWidgetHead site CssBuilder 
ToWidgetMedia site CssBuilder 
ToWidget site CssBuilder 
(~) * render (RY site) => ToWidgetHead site (render -> CssBuilder) 
(~) * render (RY site) => ToWidgetMedia site (render -> CssBuilder) 
(~) * render (RY site) => ToWidget site (render -> CssBuilder) 

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

Constructors

PageContent 

Fields

pageTitle :: Html
 
pageHead :: HtmlUrl url
 
pageBody :: HtmlUrl url
 

data Content Source

Constructors

ContentBuilder !Builder !(Maybe Int)

The content and optional content length.

ContentSource !(Source (ResourceT IO) (Flush Builder)) 
ContentFile !FilePath !(Maybe FilePart) 
ContentDontEvaluate !Content 

type RepHtml = Html Source

Deprecated: Please use Html instead

newtype DontFullyEvaluate a Source

Prevents a response body from being fully evaluated before sending the request.

Since 1.1.0

Constructors

DontFullyEvaluate 

Fields

unDontFullyEvaluate :: a
 

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.

data Header Source

Headers to be added to a Result.

data Location url Source

Constructors

Local url 
Remote Text 

Instances

Eq url => Eq (Location url) 
Show url => Show (Location url) 

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.

Constructors

UniqueList ([x] -> [x]) 

Instances

data Script url Source

Constructors

Script 

Fields

scriptLocation :: Location url
 
scriptAttributes :: [(Text, Text)]
 

Instances

Eq url => Eq (Script url) 
Show url => Show (Script url) 

data Stylesheet url Source

Constructors

Stylesheet 

Fields

styleLocation :: Location url
 
styleAttributes :: [(Text, Text)]
 

Instances

Eq url => Eq (Stylesheet url) 
Show url => Show (Stylesheet url) 

newtype Title Source

Constructors

Title 

Fields

unTitle :: Html
 

newtype Head url Source

Constructors

Head (HtmlUrl url) 

Instances

Monoid (Head url) 

newtype Body url Source

Constructors

Body (HtmlUrl url) 

Instances

Monoid (Body url) 

type CssBuilderUrl a = (a -> [(Text, Text)] -> Text) -> Builder Source

data GWData a Source

Constructors

GWData 

Instances

data Logger Source

Constructors

Logger 

Fields

loggerSet :: !LoggerSet
 
loggerDate :: !DateCacheGetter
 

loggerPutStr :: Logger -> LogStr -> IO () Source