yesod-auth-account-1.4.3: An account authentication plugin for Yesod

Safe HaskellNone
LanguageHaskell98

Yesod.Auth.Account

Contents

Description

An auth plugin for accounts. Each account consists of a username, email, and password.

This module is designed so that you can use the default pages for login, account creation, change password, etc. But the module also exports some forms which you can embed into your own pages, customizing the account process. The minimal requirements to use this module are:

  • If you are not using persistent or just want more control over the user data, you can use any datatype for user information and make it an instance of UserCredentials. You must also create an instance of AccountDB.
  • You may use a user datatype created by persistent, in which case you can make the datatype an instance of PersistUserCredentials instead of UserCredentials. In this case, AccountPersistDB from this module already implements the AccountDB interface for you.
  • Make your master site an instance of AccountSendEmail. By default, this class just logs a message so during development this class requires no implementation.
  • Make your master site and database an instance of YesodAuthAccount. There is only one required function which must be implemented (runAccountDB) although there are several functions you can override in this class to customize the behavior of this module.
  • Include accountPlugin in the list of plugins in your instance of YesodAuth.

Synopsis

Plugin

type Username = Text Source #

Each user is uniquely identified by a username.

newAccountR :: AuthRoute Source #

Route for the default new account page.

See the New Account section below for customizing the new account process.

resetPasswordR :: AuthRoute Source #

Route for the reset password page.

This page allows the user to reset their password by requesting an email with a reset URL be sent to them. See the Password Reset section below for customization.

accountPlugin :: YesodAuthAccount db master => AuthPlugin master Source #

The account authentication plugin. Here is a complete example using persistent 2.1 and yesod 1.4.

{-# LANGUAGE QuasiQuotes, TypeFamilies, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, TemplateHaskell, OverloadedStrings #-}
{-# LANGUAGE GADTs, MultiParamTypeClasses, TypeSynonymInstances #-}

import Data.Text (Text)
import Data.ByteString (ByteString)
import Database.Persist.Sqlite
import Control.Monad.Logger (runStderrLoggingT)
import Yesod
import Yesod.Auth
import Yesod.Auth.Account

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistUpperCase|
User
    username Text
    UniqueUsername username
    password ByteString
    emailAddress Text
    verified Bool
    verifyKey Text
    resetPasswordKey Text
    deriving Show
|]

instance PersistUserCredentials User where
    userUsernameF = UserUsername
    userPasswordHashF = UserPassword
    userEmailF = UserEmailAddress
    userEmailVerifiedF = UserVerified
    userEmailVerifyKeyF = UserVerifyKey
    userResetPwdKeyF = UserResetPasswordKey
    uniqueUsername = UniqueUsername

    userCreate name email key pwd = User name pwd email False key ""

data MyApp = MyApp ConnectionPool

mkYesod "MyApp" [parseRoutes|
/ HomeR GET
/auth AuthR Auth getAuth
|]

instance Yesod MyApp

instance RenderMessage MyApp FormMessage where
    renderMessage _ _ = defaultFormMessage

instance YesodPersist MyApp where
    type YesodPersistBackend MyApp = SqlBackend
    runDB action = do
        MyApp pool <- getYesod
        runSqlPool action pool

instance YesodAuth MyApp where
    type AuthId MyApp = Username
    getAuthId = return . Just . credsIdent
    loginDest _ = HomeR
    logoutDest _ = HomeR
    authPlugins _ = [accountPlugin]
    authHttpManager _ = error "No manager needed"
    onLogin = return ()
    maybeAuthId = lookupSession credsKey

instance AccountSendEmail MyApp

instance YesodAuthAccount (AccountPersistDB MyApp User) MyApp where
    runAccountDB = runAccountPersistDB

getHomeR :: Handler Html
getHomeR = do
    maid <- maybeAuthId
    case maid of
        Nothing -> defaultLayout $ [whamlet|
<p>Please visit the <a href="@{AuthR LoginR}">Login page</a>
|]
        Just u -> defaultLayout $ [whamlet|
<p>You are logged in as #{u}
<p><a href="@{AuthR LogoutR}">Logout</a>
|]

main :: IO ()
main = runStderrLoggingT $ withSqlitePool "test.db3" 10 $ \pool -> do
    runSqlPool (runMigration migrateAll) pool
    liftIO $ warp 3000 $ MyApp pool

Login

data LoginData Source #

The data collected in the login form.

Constructors

LoginData 

loginForm :: (MonadHandler m, YesodAuthAccount db master, HandlerSite m ~ master) => AForm m LoginData Source #

The login form.

You can embed this form into your own pages if you want a custom rendering of this form or to include a login form on your own pages. The form submission should be posted to loginFormPostTargetR.

loginFormPostTargetR :: AuthRoute Source #

The POST target for the loginForm.

loginWidget :: YesodAuthAccount db master => (Route Auth -> Route master) -> WidgetT master IO () Source #

A default rendering of loginForm using renderDivs.

This is the widget used in the default implementation of loginHandler. The widget also includes links to the new account and reset password pages.

New Account

The new account process works as follows.

  • A GET to newAccountR displays a form requesting account information from the user. The specific page to display can be customized by implementing getNewAccountR. By default, this is the content of newAccountForm which consists of an username, email, and a password. The target for the form is a POST to newAccountR.
  • A POST to newAccountR handles the account creation. By default, postNewAccountR processes newAccountForm and then calls createNewAccount to create the account in the database, generate a random key, and send an email with the verification key. If you have modified getNewAccountR to add additional fields to the new account form (for example CAPTCHA or other account info), you can override postNewAccountR to handle the form. You should still call createNewAccount from your own processing function.
  • The verification email includes a URL to verifyR. A GET to verifyR checks if the key matches, and if so updates the database and uses setCreds to log the user in and redirects to loginDest. If an error occurs, a message is set and the user is redirected to LoginR.
  • A POST to resendVerifyR of resendVerifyEmailForm will generate a new verification key and resend the email. By default, unregisteredLogin displays the form for resending the email.

verifyR Source #

Arguments

:: Username 
-> Text

The verification key

-> AuthRoute 

The URL sent in an email for email verification

newAccountForm :: (YesodAuthAccount db master, MonadHandler m, HandlerSite m ~ master) => AForm m NewAccountData Source #

The new account form.

You can embed this form into your own pages or into getNewAccountR. The form submission should be posted to newAccountR. Alternatively, you could embed this form into a larger form where you prompt for more information during account creation. In this case, the NewAccountData should be passed to createNewAccount from inside postNewAccountR.

newAccountWidget :: YesodAuthAccount db master => (Route Auth -> Route master) -> WidgetT master IO () Source #

A default rendering of the newAccountForm using renderDivs.

createNewAccount :: YesodAuthAccount db master => NewAccountData -> (Route Auth -> Route master) -> HandlerT master IO (UserAccount db) Source #

An action to create a new account.

You can use this action inside your own implementation of postNewAccountR if you add additional fields to the new account creation. This action assumes the user has not yet been created in the database and will create the user, so this action should be run first in your handler. Note that this action does not check if the passwords are equal. If an error occurs (username exists, etc.) this will set a message and redirect to newAccountR.

resendVerifyEmailForm :: (RenderMessage master FormMessage, MonadHandler m, HandlerSite m ~ master) => Username -> AForm m Username Source #

A form to allow the user to request the email validation be resent.

Intended for use in unregisteredLogin. The result should be posted to resendVerifyR.

resendVerifyR :: AuthRoute Source #

The POST target for resending a verification email

resendVerifyEmailWidget :: YesodAuthAccount db master => Username -> (Route Auth -> Route master) -> WidgetT master IO () Source #

A default rendering of resendVerifyEmailForm

Password Reset

This plugin implements password reset by sending the user an email containing a URL. When the user visits this URL, they are prompted for a new password. This works as follows:

  • A GET to resetPasswordR displays a form prompting for username, which when submitted sends a post to resetPasswordR. You can customize this page by overriding getResetPasswordR or by embedding resetPasswordForm into your own page and not linking your users to this URL.
  • A POST to resetPasswordR of resetPasswordForm creates a new key, stores it in the database, and sends an email. It then sets a message and redirects to the login page. You can redirect somewhere else (or carry out other actions) at the end of sendNewPasswordEmail. The URL sent in the email is setPasswordR.
  • A GET to newPasswordR checks if the key in the URL is correct and if so displays a form where the user can set a new password. The key is set as a hidden field in this form. You can customize the look of this page by overriding setPasswordHandler.
  • A POST to setPasswordR of resetPasswordForm checks if the key is correct and if so, resets the password. It then calls setCreds to successfully log in and so redirects to loginDest.
  • You can set allowPasswordReset to False, in which case the relevant routes in this plugin return 404. You can then implement password reset yourself.

newPasswordR Source #

Arguments

:: Username 
-> Text

The verification key

-> AuthRoute 

The URL sent in an email when the user requests to reset their password

resetPasswordForm :: (YesodAuthAccount db master, MonadHandler m, HandlerSite m ~ master) => AForm m Username Source #

A form for the user to request that an email be sent to them to allow them to reset their password. This form contains a field for the username (plus the CSRF token). The form should be posted to resetPasswordR.

resetPasswordWidget :: YesodAuthAccount db master => (Route Auth -> Route master) -> WidgetT master IO () Source #

A default rendering of resetPasswordForm.

newPasswordForm Source #

Arguments

:: (YesodAuth master, RenderMessage master FormMessage, MonadHandler m, HandlerSite m ~ master) 
=> Username 
-> Text

key

-> AForm m NewPasswordData 

The form for setting a new password. It contains hidden fields for the username and key and prompts for the passwords. This form should be posted to setPasswordR.

setPasswordR :: AuthRoute Source #

The POST target for reseting the password

newPasswordWidget :: YesodAuthAccount db master => UserAccount db -> (Route Auth -> Route master) -> WidgetT master IO () Source #

A default rendering of newPasswordForm.

Database and Email

class UserCredentials u where Source #

Interface for the data type which stores the user info when not using persistent.

You must make a data type that is either an instance of this class or of PersistUserCredentials, depending on if you are using persistent or not.

Users are uniquely identified by their username, and for each user we must store the email, the verify status, a hashed user password, and a reset password key. The format for the hashed password is the format from Crypto.PasswordStore. If the email has been verified and no password reset is in progress, the relevent keys should be the empty string.

class PersistUserCredentials u where Source #

Interface for the data type which stores the user info when using persistent.

You must make a data type that is either an instance of this class or of UserCredentials, depending on if you are using persistent or not.

class AccountDB m where Source #

These are the database operations to load and update user data.

Persistent users can use AccountPersistDB and don't need to create their own instance. If you are not using persistent or are using persistent but want to customize the database activity, you must manually make a monad an instance of this class. You can use any monad for which you can write runAccountDB, but typically the monad will be a newtype of HandlerT. For example,

newtype MyAccountDB a = MyAccountDB {runMyAccountDB :: HandlerT MyApp IO a}
   deriving (Monad, MonadIO)
instance AccountDB MyAccountDB where
    ....

Associated Types

type UserAccount m Source #

The data type which stores the user. Must be an instance of UserCredentials.

Methods

loadUser :: Username -> m (Maybe (UserAccount m)) Source #

Load a user by username

addNewUser :: Username -> Text -> Text -> ByteString -> m (Either Text (UserAccount m)) Source #

Create new account. The password reset key should be added as an empty string. The creation can fail with an error message, in which case the error is set in a message and the post handler redirects to newAccountR.

verifyAccount :: UserAccount m -> m () Source #

Mark the account as successfully verified. This should reset the email validation key to the empty string.

setVerifyKey :: UserAccount m -> Text -> m () Source #

Change/set the users email verification key.

setNewPasswordKey :: UserAccount m -> Text -> m () Source #

Change/set the users password reset key.

setNewPassword :: UserAccount m -> ByteString -> m () Source #

Set a new hashed password. This should also set the password reset key to the empty string.

Instances

(Yesod master, PersistUserCredentials user) => AccountDB (AccountPersistDB master user) Source # 

Associated Types

type UserAccount (AccountPersistDB master user :: * -> *) :: * Source #

class AccountSendEmail master where Source #

A class to send email.

Both of the methods are implemented by default to just log a message, so during development there are no required methods. For production, I recommend http://hackage.haskell.org/package/mime-mail.

Persistent

data AccountPersistDB master user a Source #

A newtype which when using persistent is an instance of AccountDB.

Instances

Monad (AccountPersistDB master user) Source # 

Methods

(>>=) :: AccountPersistDB master user a -> (a -> AccountPersistDB master user b) -> AccountPersistDB master user b #

(>>) :: AccountPersistDB master user a -> AccountPersistDB master user b -> AccountPersistDB master user b #

return :: a -> AccountPersistDB master user a #

fail :: String -> AccountPersistDB master user a #

Functor (AccountPersistDB master user) Source # 

Methods

fmap :: (a -> b) -> AccountPersistDB master user a -> AccountPersistDB master user b #

(<$) :: a -> AccountPersistDB master user b -> AccountPersistDB master user a #

Applicative (AccountPersistDB master user) Source # 

Methods

pure :: a -> AccountPersistDB master user a #

(<*>) :: AccountPersistDB master user (a -> b) -> AccountPersistDB master user a -> AccountPersistDB master user b #

(*>) :: AccountPersistDB master user a -> AccountPersistDB master user b -> AccountPersistDB master user b #

(<*) :: AccountPersistDB master user a -> AccountPersistDB master user b -> AccountPersistDB master user a #

MonadIO (AccountPersistDB master user) Source # 

Methods

liftIO :: IO a -> AccountPersistDB master user a #

(Yesod master, PersistUserCredentials user) => AccountDB (AccountPersistDB master user) Source # 

Associated Types

type UserAccount (AccountPersistDB master user :: * -> *) :: * Source #

type UserAccount (AccountPersistDB master user) Source # 
type UserAccount (AccountPersistDB master user) = Entity user

runAccountPersistDB :: (Yesod master, YesodPersist master, PersistEntity user, PersistUserCredentials user, b ~ YesodPersistBackend master, b ~ PersistEntityBackend user, PersistUnique b, b ~ BaseBackend b, YesodAuthAccount db master, db ~ AccountPersistDB master user) => AccountPersistDB master user a -> HandlerT master IO a Source #

Use this for runAccountDB if you are using AccountPersistDB as your database type.

Customization

class (YesodAuth master, AccountSendEmail master, AccountDB db, UserCredentials (UserAccount db), RenderMessage master FormMessage) => YesodAuthAccount db master | master -> db where Source #

The main class controlling the account plugin.

You must make your database instance of AccountDB and your master site an instance of this class. The only required method is runAccountDB, although this class contains many other methods to customize the behavior of the account plugin.

Continuing the example from the manual creation of AccountDB, a minimal instance is

instance YesodAuthAccount MyAccountDB MyApp where
    runAccountDB = runMyAccountDB

If instead you are using persistent and have made an instance of PersistUserCredentials, a minimal instance is

instance YesodAuthAccount (AccountPersistDB MyApp User) MyApp where
   runAccountDB = runAccountPersistDB

Minimal complete definition

runAccountDB

Methods

runAccountDB :: db a -> HandlerT master IO a Source #

Run a database action. This is the only required method.

checkValidUsername :: (MonadHandler m, HandlerSite m ~ master) => Username -> m (Either Text Username) Source #

A form validator for valid usernames during new account creation.

By default this allows usernames made up of isAlphaNum. You can also ignore this validation and instead validate in addNewUser, but validating here allows the validation to occur before database activity (checking existing username) and before random salt creation (requires IO).

unregisteredLogin :: UserAccount db -> HandlerT Auth (HandlerT master IO) Html Source #

What to do when the user logs in and the email has not yet been verified.

By default, this displays a message and contains resendVerifyEmailForm, allowing the user to resend the verification email. The handler is run inside the post handler for login, so you can call setCreds to preform a successful login.

getNewAccountR :: HandlerT Auth (HandlerT master IO) Html Source #

The new account page.

This is the page which is displayed on a GET to newAccountR, and defaults to an embedding of newAccountWidget.

postNewAccountR :: HandlerT Auth (HandlerT master IO) Html Source #

Handles new account creation.

By default, this processes newAccountForm, calls createNewAccount, sets a message and redirects to LoginR. If an error occurs, a message is set and the user is redirected to newAccountR.

allowPasswordReset :: master -> Bool Source #

Should the password reset inside this plugin be allowed? Defaults to True

getResetPasswordR :: HandlerT Auth (HandlerT master IO) Html Source #

The page which prompts for a username and sends an email allowing password reset. By default, it embeds resetPasswordWidget.

setPasswordHandler :: UserAccount db -> HandlerT Auth (HandlerT master IO) Html Source #

The page which allows the user to set a new password.

This is called only when the email key has been verified as correct. By default, it embeds newPasswordWidget.

renderAccountMessage :: master -> [Text] -> AccountMsg -> Text Source #

Used for i18n of AccountMsg, defaults to defaultAccountMsg. To support multiple languages, you can implement this method using the various translations from Yesod.Auth.Account.Message.

Helpers

hashPassword :: MonadIO m => Text -> m ByteString Source #

Salt and hash a password.

verifyPassword Source #

Arguments

:: Text

password

-> ByteString

hashed password

-> Bool 

Verify a password

newVerifyKey :: MonadIO m => m Text Source #

Randomly create a new verification key.

Orphan instances

YesodAuthAccount db master => RenderMessage master AccountMsg Source # 

Methods

renderMessage :: master -> [Lang] -> AccountMsg -> Text #