Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Auth
- type AuthRoute = Route Auth
- data family Route a :: *
- data AuthPlugin master = AuthPlugin {
- apName :: Text
- apDispatch :: Method -> [Piece] -> AuthHandler master TypedContent
- apLogin :: (Route Auth -> Route master) -> WidgetT master IO ()
- getAuth :: a -> Auth
- class (Yesod master, PathPiece (AuthId master), RenderMessage master FormMessage) => YesodAuth master where
- type AuthId master
- class (YesodAuth master, YesodPersist master) => YesodAuthPersist master where
- type AuthEntity master :: *
- data Creds master = Creds {
- credsPlugin :: Text
- credsIdent :: Text
- credsExtra :: [(Text, Text)]
- setCreds :: YesodAuth master => Bool -> Creds master -> HandlerT master IO ()
- setCredsRedirect :: YesodAuth master => Creds master -> HandlerT master IO TypedContent
- clearCreds :: YesodAuth master => Bool -> HandlerT master IO ()
- loginErrorMessage :: (YesodAuth master, MonadResourceBase m) => Route master -> Text -> HandlerT master m TypedContent
- loginErrorMessageI :: (MonadResourceBase m, YesodAuth master) => Route child -> AuthMessage -> HandlerT child (HandlerT master m) TypedContent
- data AuthenticationResult master
- = Authenticated (AuthId master)
- | UserError AuthMessage
- | ServerError Text
- defaultMaybeAuthId :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (Maybe (AuthId master))
- defaultLoginHandler :: AuthHandler master Html
- maybeAuthPair :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (Maybe (AuthId master, AuthEntity master))
- maybeAuth :: (YesodAuthPersist master, val ~ AuthEntity master, Key val ~ AuthId master, PersistEntity val, Typeable val) => HandlerT master IO (Maybe (Entity val))
- requireAuthId :: YesodAuth master => HandlerT master IO (AuthId master)
- requireAuthPair :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (AuthId master, AuthEntity master)
- requireAuth :: (YesodAuthPersist master, val ~ AuthEntity master, Key val ~ AuthId master, PersistEntity val, Typeable val) => HandlerT master IO (Entity val)
- data AuthException = InvalidFacebookResponse
- type AuthHandler master a = YesodAuth master => HandlerT Auth (HandlerT master IO) a
- credsKey :: Text
- provideJsonMessage :: Monad m => Text -> Writer (Endo [ProvidedRep m]) ()
- messageJson401 :: MonadResourceBase m => Text -> HandlerT master m Html -> HandlerT master m TypedContent
- asHtml :: Html -> Html
Subsite
The type-safe URLs associated with a site argument.
RedirectUrl master (Route master) | |
((~) * key Text, (~) * val Text) => RedirectUrl master (Route master, [(key, val)]) | |
((~) * key Text, (~) * val Text) => RedirectUrl master (Route master, Map key val) | |
Eq (Route LiteApp) | |
Eq (Route WaiSubsite) | |
Eq (Route Auth) # | |
Ord (Route LiteApp) | |
Ord (Route WaiSubsite) | |
Read (Route LiteApp) | |
Read (Route WaiSubsite) | |
Read (Route Auth) # | |
Show (Route LiteApp) | |
Show (Route WaiSubsite) | |
Show (Route Auth) # | |
data Route LiteApp | |
data Route WaiSubsite | |
data Route Auth # | |
data AuthPlugin master Source #
AuthPlugin | |
|
class (Yesod master, PathPiece (AuthId master), RenderMessage master FormMessage) => YesodAuth master where Source #
authLayout :: WidgetT master IO () -> HandlerT master IO Html Source #
specify the layout. Uses defaultLayout by default
loginDest :: master -> Route master Source #
Default destination on successful login, if no other destination exists.
logoutDest :: master -> Route master Source #
Default destination on successful logout, if no other destination exists.
authenticate :: Creds master -> HandlerT master IO (AuthenticationResult master) Source #
Perform authentication based on the given credentials.
Default implementation is in terms of getAuthId
Since: 1.4.4
getAuthId :: Creds master -> HandlerT master IO (Maybe (AuthId master)) Source #
Deprecated: Define authenticate
instead; getAuthId
will be removed in the next major version
Determine the ID associated with the set of credentials.
Default implementation is in terms of authenticate
authPlugins :: master -> [AuthPlugin master] Source #
Which authentication backends to use.
loginHandler :: HandlerT Auth (HandlerT master IO) Html Source #
What to show on the login page.
By default this calls defaultLoginHandler
, which concatenates
plugin widgets and wraps the result in authLayout
. Override if
you need fancy widget containers, additional functionality, or an
entirely custom page. For example, in some applications you may
want to prevent the login page being displayed for a user who is
already logged in, even if the URL is visited explicitly; this can
be done by overriding loginHandler
in your instance declaration
with something like:
instance YesodAuth App where ... loginHandler = do ma <- lift maybeAuthId when (isJust ma) $ lift $ redirect HomeR -- or any other Handler code you want defaultLoginHandler
renderAuthMessage :: master -> [Text] -> AuthMessage -> Text Source #
Used for i18n of messages provided by this package.
redirectToReferer :: master -> Bool Source #
After login and logout, redirect to the referring page, instead of
loginDest
and logoutDest
. Default is False
.
authHttpManager :: master -> Manager Source #
Return an HTTP connection manager that is stored in the foundation
type. This allows backends to reuse persistent connections. If none of
the backends you're using use HTTP connections, you can safely return
error "authHttpManager"
here.
onLogin :: HandlerT master IO () Source #
Called on a successful login. By default, calls
addMessageI "success" NowLoggedIn
.
onLogout :: HandlerT master IO () Source #
Called on logout. By default, does nothing
maybeAuthId :: HandlerT master IO (Maybe (AuthId master)) Source #
Retrieves user credentials, if user is authenticated.
By default, this calls defaultMaybeAuthId
to get the user ID from the
session. This can be overridden to allow authentication via other means,
such as checking for a special token in a request header. This is
especially useful for creating an API to be accessed via some means
other than a browser.
Since 1.2.0
maybeAuthId :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (Maybe (AuthId master)) Source #
Retrieves user credentials, if user is authenticated.
By default, this calls defaultMaybeAuthId
to get the user ID from the
session. This can be overridden to allow authentication via other means,
such as checking for a special token in a request header. This is
especially useful for creating an API to be accessed via some means
other than a browser.
Since 1.2.0
onErrorHtml :: MonadResourceBase m => Route master -> Text -> HandlerT master m Html Source #
Called on login error for HTTP requests. By default, calls
addMessage
with "error" as status and redirects to dest
.
runHttpRequest :: Request -> (Response BodyReader -> HandlerT master IO a) -> HandlerT master IO a Source #
runHttpRequest gives you a chance to handle an HttpException and retry The default behavior is to simply execute the request which will throw an exception on failure
The HTTP Request
is given in case it is useful to change behavior based on inspecting the request.
This is an experimental API that is not broadly used throughout the yesod-auth code base
class (YesodAuth master, YesodPersist master) => YesodAuthPersist master where Source #
Class which states that the given site is an instance of YesodAuth
and that its AuthId
is a lookup key for the full user information in
a YesodPersist
database.
The default implementation of getAuthEntity
assumes that the AuthId
for the YesodAuth
superclass is in fact a persistent Key
for the
given value. This is the common case in Yesod, and means that you can
easily look up the full information on a given user.
Since 1.4.0
type AuthEntity master :: * Source #
If the AuthId
for a given site is a persistent ID, this will give the
value for that entity. E.g.:
type AuthId MySite = UserId AuthEntity MySite ~ User
Since 1.2.0
getAuthEntity :: AuthId master -> HandlerT master IO (Maybe (AuthEntity master)) Source #
getAuthEntity :: (YesodPersistBackend master ~ backend, PersistRecordBackend (AuthEntity master) backend, Key (AuthEntity master) ~ AuthId master, PersistStore backend) => AuthId master -> HandlerT master IO (Maybe (AuthEntity master)) Source #
Plugin interface
User credentials
Creds | |
|
:: YesodAuth master | |
=> Bool | if HTTP redirects should be done |
-> Creds master | new credentials |
-> HandlerT master IO () |
Sets user credentials for the session after checking them with authentication backends.
:: YesodAuth master | |
=> Creds master | new credentials |
-> HandlerT master IO TypedContent |
:: YesodAuth master | |
=> Bool | if HTTP redirect to |
-> HandlerT master IO () |
Clears current user credentials for the session.
Since 1.1.7
loginErrorMessage :: (YesodAuth master, MonadResourceBase m) => Route master -> Text -> HandlerT master m TypedContent Source #
For HTML, set the message and redirect to the route. For JSON, send the message and a 401 status
loginErrorMessageI :: (MonadResourceBase m, YesodAuth master) => Route child -> AuthMessage -> HandlerT child (HandlerT master m) TypedContent Source #
User functions
data AuthenticationResult master Source #
The result of an authentication based on credentials
Since 1.4.4
Authenticated (AuthId master) | Authenticated successfully |
UserError AuthMessage | Invalid credentials provided by user |
ServerError Text | Some other error |
defaultMaybeAuthId :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (Maybe (AuthId master)) Source #
Retrieves user credentials from the session, if user is authenticated.
This function does not confirm that the credentials are valid, see
maybeAuthIdRaw
for more information.
Since 1.1.2
defaultLoginHandler :: AuthHandler master Html Source #
Default handler to show the login page.
This is the default loginHandler
. It concatenates plugin widgets and
wraps the result in authLayout
. See loginHandler
for more details.
Since 1.4.9
maybeAuthPair :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (Maybe (AuthId master, AuthEntity master)) Source #
Similar to maybeAuth
, but doesn’t assume that you are using a
Persistent database.
Since 1.4.0
maybeAuth :: (YesodAuthPersist master, val ~ AuthEntity master, Key val ~ AuthId master, PersistEntity val, Typeable val) => HandlerT master IO (Maybe (Entity val)) Source #
Similar to maybeAuthId
, but additionally look up the value associated
with the user's database identifier to get the value in the database. This
assumes that you are using a Persistent database.
Since 1.1.0
requireAuthId :: YesodAuth master => HandlerT master IO (AuthId master) Source #
Similar to maybeAuthId
, but redirects to a login page if user is not
authenticated or responds with error 401 if this is an API client (expecting JSON).
Since 1.1.0
requireAuthPair :: (YesodAuthPersist master, Typeable (AuthEntity master)) => HandlerT master IO (AuthId master, AuthEntity master) Source #
Similar to requireAuth
, but not tied to Persistent's Entity
type.
Instead, the AuthId
and AuthEntity
are returned in a tuple.
Since 1.4.0
requireAuth :: (YesodAuthPersist master, val ~ AuthEntity master, Key val ~ AuthId master, PersistEntity val, Typeable val) => HandlerT master IO (Entity val) Source #
Similar to maybeAuth
, but redirects to a login page if user is not
authenticated or responds with error 401 if this is an API client (expecting JSON).
Since 1.1.0
Exception
data AuthException Source #
Helper
Internal
Internal session key used to hold the authentication information.
Since 1.2.3
provideJsonMessage :: Monad m => Text -> Writer (Endo [ProvidedRep m]) () Source #
messageJson401 :: MonadResourceBase m => Text -> HandlerT master m Html -> HandlerT master m TypedContent Source #
Orphan instances
YesodAuth master => RenderMessage master AuthMessage Source # | |
YesodAuth master => YesodSubDispatch Auth (HandlerT master IO) Source # | |