Safe Haskell | None |
---|
- authEmail :: YesodAuthEmail m => AuthPlugin m
- class (YesodAuth site, PathPiece (AuthEmailId site), RenderMessage site AuthMessage) => YesodAuthEmail site where
- type AuthEmailId site
- addUnverified :: Email -> VerKey -> HandlerT site IO (AuthEmailId site)
- sendVerifyEmail :: Email -> VerKey -> VerUrl -> HandlerT site IO ()
- getVerifyKey :: AuthEmailId site -> HandlerT site IO (Maybe VerKey)
- setVerifyKey :: AuthEmailId site -> VerKey -> HandlerT site IO ()
- verifyAccount :: AuthEmailId site -> HandlerT site IO (Maybe (AuthId site))
- getPassword :: AuthId site -> HandlerT site IO (Maybe SaltedPass)
- setPassword :: AuthId site -> SaltedPass -> HandlerT site IO ()
- getEmailCreds :: Identifier -> HandlerT site IO (Maybe (EmailCreds site))
- getEmail :: AuthEmailId site -> HandlerT site IO (Maybe Email)
- randomKey :: site -> IO Text
- afterPasswordRoute :: site -> Route site
- needOldPassword :: AuthId site -> HandlerT site IO Bool
- checkPasswordSecurity :: AuthId site -> Text -> HandlerT site IO (Either Text ())
- confirmationEmailSentResponse :: Text -> HandlerT site IO TypedContent
- normalizeEmailAddress :: site -> Text -> Text
- registerHandler :: AuthHandler site Html
- forgotPasswordHandler :: AuthHandler site Html
- setPasswordHandler :: Bool -> AuthHandler site TypedContent
- data EmailCreds site = EmailCreds {
- emailCredsId :: AuthEmailId site
- emailCredsAuthId :: Maybe (AuthId site)
- emailCredsStatus :: VerStatus
- emailCredsVerkey :: Maybe VerKey
- emailCredsEmail :: Email
- saltPass :: Text -> IO Text
- loginR :: AuthRoute
- registerR :: AuthRoute
- forgotPasswordR :: AuthRoute
- setpassR :: AuthRoute
- isValidPass :: Text -> SaltedPass -> Bool
- type Email = Text
- type VerKey = Text
- type VerUrl = Text
- type SaltedPass = Text
- type VerStatus = Bool
- type Identifier = Text
- loginLinkKey :: Text
- setLoginLinkKey :: (YesodAuthEmail site, MonadHandler m, HandlerSite m ~ site) => AuthId site -> m ()
- defaultRegisterHandler :: YesodAuthEmail master => AuthHandler master Html
- defaultForgotPasswordHandler :: YesodAuthEmail master => AuthHandler master Html
- defaultSetPasswordHandler :: YesodAuthEmail master => Bool -> AuthHandler master TypedContent
Plugin
authEmail :: YesodAuthEmail m => AuthPlugin mSource
class (YesodAuth site, PathPiece (AuthEmailId site), RenderMessage site AuthMessage) => YesodAuthEmail site whereSource
type AuthEmailId site Source
addUnverified :: Email -> VerKey -> HandlerT site IO (AuthEmailId site)Source
Add a new email address to the database, but indicate that the address has not yet been verified.
Since 1.1.0
sendVerifyEmail :: Email -> VerKey -> VerUrl -> HandlerT site IO ()Source
Send an email to the given address to verify ownership.
Since 1.1.0
getVerifyKey :: AuthEmailId site -> HandlerT site IO (Maybe VerKey)Source
Get the verification key for the given email ID.
Since 1.1.0
setVerifyKey :: AuthEmailId site -> VerKey -> HandlerT site IO ()Source
Set the verification key for the given email ID.
Since 1.1.0
verifyAccount :: AuthEmailId site -> HandlerT site IO (Maybe (AuthId site))Source
Verify the email address on the given account.
Since 1.1.0
getPassword :: AuthId site -> HandlerT site IO (Maybe SaltedPass)Source
Get the salted password for the given account.
Since 1.1.0
setPassword :: AuthId site -> SaltedPass -> HandlerT site IO ()Source
Set the salted password for the given account.
Since 1.1.0
getEmailCreds :: Identifier -> HandlerT site IO (Maybe (EmailCreds site))Source
Get the credentials for the given Identifier
, which may be either an
email address or some other identification (e.g., username).
Since 1.2.0
getEmail :: AuthEmailId site -> HandlerT site IO (Maybe Email)Source
Get the email address for the given email ID.
Since 1.1.0
randomKey :: site -> IO TextSource
Generate a random alphanumeric string.
Since 1.1.0
afterPasswordRoute :: site -> Route siteSource
Route to send user to after password has been set correctly.
Since 1.2.0
needOldPassword :: AuthId site -> HandlerT site IO BoolSource
Does the user need to provide the current password in order to set a new password?
Default: if the user logged in via an email link do not require a password.
Since 1.2.1
checkPasswordSecurity :: AuthId site -> Text -> HandlerT site IO (Either Text ())Source
Check that the given plain-text password meets minimum security standards.
Default: password is at least three characters.
confirmationEmailSentResponse :: Text -> HandlerT site IO TypedContentSource
Response after sending a confirmation email.
Since 1.2.2
normalizeEmailAddress :: site -> Text -> TextSource
Additional normalization of email addresses, besides standard canonicalization.
Default: Lower case the email address.
Since 1.2.3
registerHandler :: AuthHandler site HtmlSource
Handler called to render the registration page. The default works fine, but you may want to override it in order to have a different DOM.
Default: defaultRegisterHandler
.
Since: 1.2.6.
forgotPasswordHandler :: AuthHandler site HtmlSource
Handler called to render the "forgot password" page. The default works fine, but you may want to override it in order to have a different DOM.
Default: defaultForgotPasswordHandler
.
Since: 1.2.6.
:: Bool | Whether the old password is needed. If |
-> AuthHandler site TypedContent |
Handler called to render the "set password" page. The default works fine, but you may want to override it in order to have a different DOM.
Default: defaultSetPasswordHandler
.
Since: 1.2.6.
data EmailCreds site Source
Data stored in a database for each e-mail address.
EmailCreds | |
|
Routes
:: Text | cleartext password |
-> SaltedPass | salted password |
-> Bool |
Types
type SaltedPass = TextSource
type Identifier = TextSource
An Identifier generalizes an email address to allow users to log in with some other form of credentials (e.g., username).
Note that any of these other identifiers must not be valid email addresses.
Since 1.2.0
Misc
Session variable set when user logged in via a login link. See
needOldPassword
.
Since 1.2.1
setLoginLinkKey :: (YesodAuthEmail site, MonadHandler m, HandlerSite m ~ site) => AuthId site -> m ()Source
Set loginLinkKey
to the current time.
Since 1.2.1
Default handlers
defaultRegisterHandler :: YesodAuthEmail master => AuthHandler master HtmlSource
Default implementation of registerHandler
.
Since: 1.2.6
defaultForgotPasswordHandler :: YesodAuthEmail master => AuthHandler master HtmlSource
Default implementation of forgotPasswordHandler
.
Since: 1.2.6
defaultSetPasswordHandler :: YesodAuthEmail master => Bool -> AuthHandler master TypedContentSource
Default implementation of setPasswordHandler
.
Since: 1.2.6