snap-1.0.0.2: Top-level package for the Snap Web Framework

Safe HaskellNone
LanguageHaskell98

Snap.Snaplet.Auth

Contents

Description

This module contains all the central authentication functionality.

It exports a number of high-level functions to be used directly in your application handlers.

We also export a number of mid-level functions that should be helpful when you are integrating with another way of confirming the authentication of login requests.

Synopsis

Higher Level Handler Functions

createUser Source #

Arguments

:: Text

Username

-> ByteString

Password

-> Handler b (AuthManager b) (Either AuthFailure AuthUser) 

Create a new user from just a username and password

usernameExists Source #

Arguments

:: Text

The username to be checked

-> Handler b (AuthManager b) Bool 

Check whether a user with the given username exists.

saveUser :: AuthUser -> Handler b (AuthManager b) (Either AuthFailure AuthUser) Source #

Create or update a given user

destroyUser :: AuthUser -> Handler b (AuthManager b) () Source #

Destroy the given user

loginByUsername Source #

Arguments

:: Text

Username/login for user

-> Password

Should be ClearText

-> Bool

Set remember token?

-> Handler b (AuthManager b) (Either AuthFailure AuthUser) 

Lookup a user by her username, check given password and perform login

loginByRememberToken :: Handler b (AuthManager b) (Either AuthFailure AuthUser) Source #

Remember user from the remember token if possible and perform login

forceLogin Source #

Arguments

:: AuthUser

An existing user, somehow looked up from db

-> Handler b (AuthManager b) (Either AuthFailure ()) 

Login and persist the given AuthUser in the active session

Meant to be used if you have other means of being sure that the person is who she says she is.

logout :: Handler b (AuthManager b) () Source #

Logout the active user

currentUser :: Handler b (AuthManager b) (Maybe AuthUser) Source #

Return the current user; trying to remember from cookie if possible.

isLoggedIn :: Handler b (AuthManager b) Bool Source #

Convenience wrapper around rememberUser that returns a bool result

Lower Level Functions

markAuthSuccess :: AuthUser -> Handler b (AuthManager b) (Either AuthFailure AuthUser) Source #

Mutate an AuthUser, marking successful authentication

This will save the user to the backend.

markAuthFail :: AuthUser -> Handler b (AuthManager b) (Either AuthFailure AuthUser) Source #

Mutate an AuthUser, marking failed authentication

This will save the user to the backend.

checkPasswordAndLogin Source #

Arguments

:: AuthUser

An existing user, somehow looked up from db

-> Password

A ClearText password

-> Handler b (AuthManager b) (Either AuthFailure AuthUser) 

Authenticate and log the user into the current session if successful.

This is a mid-level function exposed to allow roll-your-own ways of looking up a user from the database.

This function will:

  1. Check the password
  2. Login the user into the current session
  3. Mark success/failure of the authentication trial on the user record

Types

data AuthManager b Source #

Abstract data type holding all necessary information for auth operation

Constructors

IAuthBackend r => AuthManager 

Fields

class IAuthBackend r where Source #

All storage backends need to implement this typeclass

Methods

save :: r -> AuthUser -> IO (Either AuthFailure AuthUser) Source #

Create or update the given AuthUser record. A userId of Nothing indicates that a new user should be created, otherwise the user information for that userId should be updated.

lookupByUserId :: r -> UserId -> IO (Maybe AuthUser) Source #

lookupByLogin :: r -> Text -> IO (Maybe AuthUser) Source #

lookupByRememberToken :: r -> Text -> IO (Maybe AuthUser) Source #

destroy :: r -> AuthUser -> IO () Source #

data AuthSettings Source #

Authentication settings defined at initialization time

Constructors

AuthSettings 

Fields

defAuthSettings :: AuthSettings Source #

Default settings for Auth.

asMinPasswdLen = 8
asRememberCookieName = "_remember"
asRememberPeriod = Just (2*7*24*60*60) = 2 weeks
asLockout = Nothing
asSiteKey = "site_key.txt"

defAuthUser :: AuthUser Source #

Default AuthUser that has all empty values.

newtype UserId Source #

Internal representation of a User. By convention, we demand that the application is able to directly fetch a User using this identifier.

Think of this type as a secure, authenticated user. You should normally never see this type unless a user has been authenticated.

Constructors

UserId 

Fields

data AuthFailure Source #

Authentication failures indicate what went wrong during authentication. They may provide useful information to the developer, although it is generally not advisable to show the user the exact details about why login failed.

data Role Source #

This will be replaced by a role-based permission system.

Constructors

Role ByteString 

Other Utilities

authSettingsFromConfig :: Initializer b v AuthSettings Source #

Function to get auth settings from a config file. This function can be used by the authors of auth snaplet backends in the initializer to let the user configure the auth snaplet from a config file. All options are optional and default to what's in defAuthSettings if not supplied. Here's what the default options would look like in the config file:

minPasswordLen = 8
rememberCookie = "_remember"
rememberPeriod = 1209600 # 2 weeks
lockout = [5, 86400] # 5 attempts locks you out for 86400 seconds
siteKey = "site_key.txt"

withBackend Source #

Arguments

:: (forall r. IAuthBackend r => r -> Handler b (AuthManager v) a)

The function to run with the handler.

-> Handler b (AuthManager v) a 

Run a function on the backend, and return the result.

This uses an existential type so that the backend type doesn't escape AuthManager. The reason that the type is Handler b (AuthManager v) a and not a is because anything that uses the backend will return an IO something, which you can liftIO, or a Handler b (AuthManager v) a if it uses other handler things.

encryptPassword :: Password -> IO Password Source #

Turn a ClearText password into an Encrypted password, ready to be stuffed into a database.

authenticatePassword Source #

Arguments

:: AuthUser

Looked up from the back-end

-> Password

Check against this password

-> Maybe AuthFailure 

Check password for a given user.

Returns Nothing if check is successful and an IncorrectPassword error otherwise

setPassword :: AuthUser -> ByteString -> IO AuthUser Source #

Set a new password for the given user. Given password should be clear-text; it will be encrypted into a Encrypted.

encrypt :: ByteString -> IO ByteString Source #

The underlying encryption function, in case you need it for external processing.

verify Source #

Arguments

:: ByteString

Cleartext

-> ByteString

Encrypted reference

-> Bool 

The underlying verify function, in case you need it for external processing.

Handlers

registerUser Source #

Arguments

:: ByteString

Login field

-> ByteString

Password field

-> Handler b (AuthManager b) (Either AuthFailure AuthUser) 

Register a new user by specifying login and password Param fields

loginUser Source #

Arguments

:: ByteString

Username field

-> ByteString

Password field

-> Maybe ByteString

Remember field; Nothing if you want no remember function.

-> (AuthFailure -> Handler b (AuthManager b) ())

Upon failure

-> Handler b (AuthManager b) ()

Upon success

-> Handler b (AuthManager b) () 

A MonadSnap handler that processes a login form.

The request paremeters are passed to performLogin

To make your users stay logged in for longer than the session replay prevention timeout, you must pass a field name as the third parameter and that field must be set to a value of "1" by the submitting form. This lets you use a user selectable check box. Or if you want user remembering always turned on, you can use a hidden form field.

logoutUser Source #

Arguments

:: Handler b (AuthManager b) ()

What to do after logging out

-> Handler b (AuthManager b) () 

Simple handler to log the user out. Deletes user from session.

requireUser Source #

Arguments

:: SnapletLens b (AuthManager b)

Lens reference to an AuthManager

-> Handler b v a

Do this if no authenticated user is present.

-> Handler b v a

Do this if an authenticated user is present.

-> Handler b v a 

Require that an authenticated AuthUser is present in the current session.

This function has no DB cost - only checks to see if a user_id is present in the current session.

setPasswordResetToken :: Text -> Handler b (AuthManager b) (Maybe Text) Source #

This function generates a random password reset token and stores it in the database for the user. Call this function when a user forgets their password. Then use the token to autogenerate a link that the user can visit to reset their password. This function also sets a timestamp so the reset token can be expired.

clearPasswordResetToken :: Text -> Handler b (AuthManager b) Bool Source #

Clears a user's password reset token. Call this when the user successfully changes their password to ensure that the password reset link cannot be used again.

Splice helpers

addAuthSplices Source #

Arguments

:: HasHeist b 
=> Snaplet (Heist b) 
-> SnapletLens b (AuthManager b)

A lens reference to AuthManager

-> Initializer b v () 

Add all standard auth splices to a Heist-enabled application.

This adds the following splices: <ifLoggedIn> <ifLoggedOut> <loggedInUser>

compiledAuthSplices :: SnapletLens b (AuthManager b) -> Splices (SnapletCSplice b) Source #

List containing compiled splices for ifLoggedIn, ifLoggedOut, and loggedInUser.

userCSplices :: Monad m => Splices (RuntimeSplice m AuthUser -> Splice m) Source #

Compiled splices for AuthUser.

userISplices :: Monad m => AuthUser -> Splices (Splice m) Source #

Function to generate interpreted splices from an AuthUser.

ifLoggedIn :: SnapletLens b (AuthManager b) -> SnapletISplice b Source #

A splice that can be used to check for existence of a user. If a user is present, this will run the contents of the node.

<ifLoggedIn> Show this when there is a logged in user </ifLoggedIn>

ifLoggedOut :: SnapletLens b (AuthManager b) -> SnapletISplice b Source #

A splice that can be used to check for absence of a user. If a user is not present, this will run the contents of the node.

<ifLoggedOut> Show this when there is a logged in user </ifLoggedOut>

loggedInUser :: SnapletLens b (AuthManager b) -> SnapletISplice b Source #

A splice that will simply print the current user's login, if there is one.