serversession-frontend-wai-1.0.1: wai-session bindings for serversession.
Safe HaskellNone
LanguageHaskell2010

Web.ServerSession.Frontend.Wai

Description

wai-session server-side session support.

Please note that this frontend has some limitations:

  • Cookies use the Max-age field instead of Expires. The Max-age field is not supported by all browsers: some browsers will treat them as non-persistent cookies.
  • Also, the Max-age is fixed and does not take a given session into consideration.
Synopsis

Simple interface

withServerSession Source #

Arguments

:: (Functor m, MonadIO m, MonadIO n, Storage sto, SessionData sto ~ SessionMap) 
=> Key (Session m Text ByteString)

Vault key to use when passing the session through.

-> (State sto -> State sto)

Set any options on the serversession state.

-> sto

Storage backend.

-> n Middleware 

Construct the wai-session middleware using the given storage backend and options. This is a convenient function that uses withSession, createState, sessionStore, getCookieName and createCookieTemplate.

Invalidating session IDs

forceInvalidate :: Session m Text ByteString -> ForceInvalidate -> m () Source #

Invalidate the current session ID (and possibly more, check ForceInvalidate). This is useful to avoid session fixation attacks (cf. http://www.acrossecurity.com/papers/session_fixation.pdf).

data ForceInvalidate #

Which session IDs should be invalidated.

Note that this is not the same concept of invalidation as used on J2EE. In this context, invalidation means creating a fresh session ID for this user's session and disabling the old ID. Its purpose is to avoid session fixation attacks.

Constructors

CurrentSessionId

Invalidate the current session ID. The current session ID is automatically invalidated on login and logout (cf. setAuthKey).

AllSessionIdsOfLoggedUser

Invalidate all session IDs beloging to the currently logged in user. Only the current session ID will be renewed (the only one for which a cookie can be set).

This is useful, for example, if the user asks to change their password. It's also useful to provide a button to clear all other sessions.

If the user is not logged in, this option behaves exactly as CurrentSessionId (i.e., it does not invalidate the sessions of all logged out users).

Note that, for the purposes of AllSessionIdsOfLoggedUser, we consider "logged user" the one that is logged in at the *end* of the handler processing. For example, if the user was logged in but the current handler logged him out, the session IDs of the user who was logged in will not be invalidated.

DoNotForceInvalidate

Do not force invalidate. Invalidate only if automatically. This is the default.

Instances

Instances details
Bounded ForceInvalidate 
Instance details

Defined in Web.ServerSession.Core.Internal

Enum ForceInvalidate 
Instance details

Defined in Web.ServerSession.Core.Internal

Eq ForceInvalidate 
Instance details

Defined in Web.ServerSession.Core.Internal

Ord ForceInvalidate 
Instance details

Defined in Web.ServerSession.Core.Internal

Read ForceInvalidate 
Instance details

Defined in Web.ServerSession.Core.Internal

Show ForceInvalidate 
Instance details

Defined in Web.ServerSession.Core.Internal

Flexible interface

sessionStore Source #

Arguments

:: (Functor m, MonadIO m, Storage sto, KeyValue (SessionData sto)) 
=> State sto

serversession state, incl. storage backend.

-> SessionStore m (Key (SessionData sto)) (Value (SessionData sto))

wai-session session store.

Construct the wai-session session store using the given state. Note that keys and values types are fixed.

As wai-session always requires a value to be provided, we return an empty ByteString when the empty session was not saved.

createCookieTemplate :: State sto -> SetCookie Source #

Create a cookie template given a state.

Since we don't have access to the Session, we can't fill the Expires field. Besides, as the template is constant, eventually the Expires field would become outdated. This is a limitation of wai-session's interface, not a serversession limitation. Other frontends support the Expires field.

Instead, we fill only the Max-age field. It works fine for modern browsers, but many don't support it and will treat the cookie as non-persistent (notably IE 6, 7 and 8).

class IsSessionData sess => KeyValue sess where Source #

Class for session data types that can be used as key-value stores.

Associated Types

type Key sess :: Type Source #

type Value sess :: Type Source #

Methods

kvLookup :: Key sess -> sess -> Maybe (Value sess) Source #

kvInsert :: Key sess -> Value sess -> sess -> sess Source #

State configuration

setCookieName :: Text -> State sto -> State sto #

Set the name of cookie where the session ID will be saved. Defaults to "JSESSIONID", which is a generic cookie name used by many frameworks thus making it harder to fingerprint this implementation.

setAuthKey :: Text -> State sto -> State sto #

Set the name of the session variable that keeps track of the logged user.

This setting is used by session data types that are Map-alike, using a lookup function. However, the IsSessionData instance of a session data type may choose not to use it. For example, if you implemented a custom data type, you could return the AuthId without needing a lookup.

Defaults to "_ID" (used by yesod-auth).

setIdleTimeout :: Maybe NominalDiffTime -> State sto -> State sto #

Set the idle timeout for all sessions. This is used both on the client side (by setting the cookie expires fields) and on the server side (the idle timeout is enforced even if the cookie expiration is ignored). Setting to Nothing removes the idle timeout entirely.

"[The idle timemout] defines the amount of time a session will remain active in case there is no activity in the session, closing and invalidating the session upon the defined idle period since the last HTTP request received by the web application for a given session ID." (Source)

Defaults to 7 days.

setAbsoluteTimeout :: Maybe NominalDiffTime -> State sto -> State sto #

Set the absolute timeout for all sessions. This is used both on the client side (by setting the cookie expires fields) and on the server side (the absolute timeout is enforced even if the cookie expiration is ignored). Setting to Nothing removes the absolute timeout entirely.

"[The absolute timeout] defines the maximum amount of time a session can be active, closing and invalidating the session upon the defined absolute period since the given session was initially created by the web application. After invalidating the session, the user is forced to (re)authenticate again in the web application and establish a new session." (Source)

Defaults to 60 days.

setTimeoutResolution :: Maybe NominalDiffTime -> State sto -> State sto #

Set the timeout resolution.

We need to save both the creation and last access times on sessions in order to implement idle and absolute timeouts. This means that we have to save the updated session on the storage backend even if the request didn't change any session variable, if only to update the last access time.

This setting provides an optimization where the session is not updated on the storage backend provided that:

  • No session variables were changed.
  • The difference between the current time and the last saved access time is less than the timeout resolution.

For example, with a timeout resolution of 1 minute, every request that does not change the session variables within 1 minute of the last update will not generate any updates on the storage backend.

If the timeout resolution is Nothing, then this optimization becomes disabled and the session will always be updated.

Defaults to 10 minutes.

setPersistentCookies :: Bool -> State sto -> State sto #

Set whether by default cookies should be persistent (True) or non-persistent (False). Persistent cookies are saved across browser sessions. Non-persistent cookies are discarded when the browser is closed.

If you set cookies to be persistent and do not define any timeouts (setIdleTimeout or setAbsoluteTimeout), then the cookie is set to expire in 10 years.

Defaults to True.

setHttpOnlyCookies :: Bool -> State sto -> State sto #

Set whether cookies should be HTTP-only (True) or not (False). Cookies marked as HTTP-only ("HttpOnly") are not accessible from client-side scripting languages such as JavaScript, thus preventing a large class of XSS attacks. It's highly recommended to set this attribute to True.

Defaults to True.

setSecureCookies :: Bool -> State sto -> State sto #

Set whether cookies should be mared "Secure" (True) or not (False). Cookies marked as "Secure" are not sent via plain HTTP connections, only via HTTPS connections. It's highly recommended to set this attribute to True. However, since many sites do not operate over HTTPS, the default is False.

Defaults to False.

data State sto #

The server-side session backend needs to maintain some state in order to work:

Create a new State using createState.