serversession-1.0.2: Secure, modular server-side sessions.
Safe HaskellNone
LanguageHaskell2010

Web.ServerSession.Core.Internal

Description

Internal module exposing the guts of the package. Use at your own risk. No API stability guarantees apply.

UndecidableInstances is required in order to implement Eq, Ord, Show, etc. on data types that have Decomposed fields, and should be fairly safe.

Synopsis

Documentation

newtype SessionId sess Source #

The ID of a session. Always 18 bytes base64url-encoded as 24 characters. The sess type variable is a phantom type for the session data type this session ID points to.

Implementation notes:

Constructors

S 

Fields

Instances

Instances details
Eq (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

(==) :: SessionId sess -> SessionId sess -> Bool #

(/=) :: SessionId sess -> SessionId sess -> Bool #

Ord (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

compare :: SessionId sess -> SessionId sess -> Ordering #

(<) :: SessionId sess -> SessionId sess -> Bool #

(<=) :: SessionId sess -> SessionId sess -> Bool #

(>) :: SessionId sess -> SessionId sess -> Bool #

(>=) :: SessionId sess -> SessionId sess -> Bool #

max :: SessionId sess -> SessionId sess -> SessionId sess #

min :: SessionId sess -> SessionId sess -> SessionId sess #

Read (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Show (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

showsPrec :: Int -> SessionId sess -> ShowS #

show :: SessionId sess -> String #

showList :: [SessionId sess] -> ShowS #

Hashable (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

hashWithSalt :: Int -> SessionId sess -> Int #

hash :: SessionId sess -> Int #

ToJSON (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

FromJSON (SessionId sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

PathPiece (SessionId sess) Source #

Sanity checks input on fromPathPiece (untrusted input).

Instance details

Defined in Web.ServerSession.Core.Internal

Methods

fromPathPiece :: Text -> Maybe (SessionId sess) #

toPathPiece :: SessionId sess -> Text #

checkSessionId :: Text -> Maybe (SessionId sess) Source #

(Internal) Check that the given text is a base64url-encoded representation of 18 bytes.

generateSessionId :: Generator -> IO (SessionId sess) Source #

Securely generate a new SessionId.

type AuthId = ByteString Source #

Value of the authKey session key.

data Session sess Source #

Representation of a saved session.

This representation is used by the serversession family of packages, transferring data between this core package and storage backend packages. The sess type variable describes the session data type.

Constructors

Session 

Fields

Instances

Instances details
Eq (Decomposed sess) => Eq (Session sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

(==) :: Session sess -> Session sess -> Bool #

(/=) :: Session sess -> Session sess -> Bool #

Ord (Decomposed sess) => Ord (Session sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

compare :: Session sess -> Session sess -> Ordering #

(<) :: Session sess -> Session sess -> Bool #

(<=) :: Session sess -> Session sess -> Bool #

(>) :: Session sess -> Session sess -> Bool #

(>=) :: Session sess -> Session sess -> Bool #

max :: Session sess -> Session sess -> Session sess #

min :: Session sess -> Session sess -> Session sess #

Show (Decomposed sess) => Show (Session sess) Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Methods

showsPrec :: Int -> Session sess -> ShowS #

show :: Session sess -> String #

showList :: [Session sess] -> ShowS #

newtype SessionMap Source #

A newtype for a common session map.

This is a common representation of a session. Although serversession has generalized session data types, you can use this one if you don't want to worry about it. We strive to support this session data type on all frontends and storage backends.

class (Show (Decomposed sess), Typeable (Decomposed sess), Typeable sess) => IsSessionData sess where Source #

Class for data types to be used as session data (cf. sessionData, SessionData).

The Show constrain is needed for StorageException.

Associated Types

type Decomposed sess :: * Source #

The type of the session data after being decomposed. This may be the same as sess.

Methods

emptySession :: sess Source #

Empty session data.

decomposeSession Source #

Arguments

:: Text

The auth key (cf. setAuthKey).

-> sess

Session data to be decomposed.

-> DecomposedSession sess

Decomposed session data.

Decompose session data into:

recomposeSession Source #

Arguments

:: Text

The auth key (cf. setAuthKey).

-> Maybe AuthId

The AuthId, if any.

-> Decomposed sess

Decomposed session data to be recomposed.

-> sess

Recomposed session data.

Recompose a decomposed session again into a proper sess.

isSameDecomposed :: proxy sess -> Decomposed sess -> Decomposed sess -> Bool Source #

Returns True when both session datas are to be considered the same.

This is used to optimize storage calls (cf. setTimeoutResolution). Always returning False will disable the optimization but won't have any other adverse effects.

For data types implementing Eq, this is usually a good implementation:

isSameDecomposed _ = (==)

isDecomposedEmpty :: proxy sess -> Decomposed sess -> Bool Source #

Returns True if the decomposed session data is to be considered empty.

This is used to avoid storing empty session data if at all possible. Always returning False will disable the optimization but won't have any other adverse effects.

Instances

Instances details
IsSessionData SessionMap Source #

A SessionMap decomposes into a SessionMap minus the keys that were removed. The auth key is added back when recomposing.

Instance details

Defined in Web.ServerSession.Core.Internal

Associated Types

type Decomposed SessionMap Source #

data DecomposedSession sess Source #

A session data type sess with its special variables taken apart.

class (Typeable sto, MonadIO (TransactionM sto), IsSessionData (SessionData sto)) => Storage sto where Source #

A storage backend sto for server-side sessions. The sess session data type and/or its Decomposed version may be constrained depending on the storage backend capabilities.

Associated Types

type SessionData sto :: * Source #

The session data type used by this storage.

type TransactionM sto :: * -> * Source #

Monad where transactions happen for this backend. We do not require transactions to be ACID.

Methods

runTransactionM :: sto -> TransactionM sto a -> IO a Source #

Run a transaction on the IO monad.

getSession :: sto -> SessionId (SessionData sto) -> TransactionM sto (Maybe (Session (SessionData sto))) Source #

Get the session for the given session ID. Returns Nothing if the session is not found.

deleteSession :: sto -> SessionId (SessionData sto) -> TransactionM sto () Source #

Delete the session with given session ID. Does not do anything if the session is not found.

deleteAllSessionsOfAuthId :: sto -> AuthId -> TransactionM sto () Source #

Delete all sessions of the given auth ID. Does not do anything if there are no sessions of the given auth ID.

insertSession :: sto -> Session (SessionData sto) -> TransactionM sto () Source #

Insert a new session. Throws SessionAlreadyExists if there already exists a session with the same session ID (we only call this method after generating a fresh session ID).

replaceSession :: sto -> Session (SessionData sto) -> TransactionM sto () Source #

Replace the contents of a session. Throws SessionDoesNotExist if there is no session with the given session ID (we only call this method when updating a session that is known to exist).

It is possible to have concurrent requests using the same session ID such that:

request 1: loadSession
                       request 2: loadSession
                       request 2: forceInvalidate
                       request 2: saveSession
request 1: saveSession

The request 2's call to saveSession will have called deleteSession as invalidation was forced. However, request 1 has no idea and will try to replaceSession. The following behaviors are possible:

  1. Make replaceSession insert the session again. However, this will undo the invalidation of request 2. As invalidations are done for security reasons, this is a bad idea.
  2. Make replaceSession silently discard the session. The reasoning is that, as the session was going to be invalidated if request 2 came after request 1, we can discard its contents. However, we can't be sure that request 2 would have had the same effect if it had seen the session changes made by request 1 (and vice versa).
  3. Make replaceSession throw an error. This error is going to be unrecoverable since usually the session processing is done at the end of the request processing by the web framework, thus leading to a 500 Internal Server Error. However, this signals to the caller that something went wrong, which is correct.

Most of the time this discussion does not matter. Invalidations usually occur at times where only one request is flying.

data StorageException sto Source #

Common exceptions that may be thrown by any storage.

Constructors

SessionAlreadyExists

Exception thrown by insertSession whenever a session with same ID already exists.

SessionDoesNotExist

Exception thrown by replaceSession whenever trying to replace a session that is not present on the storage.

data State sto Source #

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

Create a new State using createState.

createState :: MonadIO m => sto -> m (State sto) Source #

Create a new State for the server-side session backend using the given storage backend.

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

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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.

loadSession :: Storage sto => State sto -> Maybe ByteString -> IO (SessionData sto, SaveSessionToken sto) Source #

Load the session map from the storage backend. The value of the session cookie should be given as argument if present.

Returns:

  • The session data sess to be used by the frontend as the current session's value.
  • Information to be passed back to saveSession on the end of the request in order to save the session.

checkExpired Source #

Arguments

:: UTCTime

Now.

-> State sto 
-> Session sess 
-> Maybe (Session sess) 

Check if a session s has expired. Returns the Just s if not expired, or Nothing if expired.

nextExpires :: State sto -> Session sess -> Maybe UTCTime Source #

Calculate the next point in time where the given session will expire assuming that it sees no activity until then. Returns Nothing iff the state does not have any expirations set to Just.

cookieExpires :: State sto -> Session sess -> Maybe UTCTime Source #

Calculate the date that should be used for the cookie's "Expires" field.

saveSession :: Storage sto => State sto -> SaveSessionToken sto -> SessionData sto -> IO (Maybe (Session (SessionData sto))) Source #

Save the session on the storage backend. A SaveSessionToken given by loadSession is expected besides the new contents of the session.

Returns Nothing if the session was empty and didn't need to be saved. Note that this does not necessarily means that nothing was done. If you ask for a session to be invalidated and clear every other sesssion variable, then saveSession will invalidate the older session but will avoid creating a new, empty one.

data SaveSessionToken sto Source #

Opaque token containing the necessary information for saveSession to save the session.

invalidateIfNeeded :: Storage sto => State sto -> Maybe (Session (SessionData sto)) -> DecomposedSession (SessionData sto) -> TransactionM sto (Maybe (Session (SessionData sto))) Source #

Invalidates an old session ID if needed. Returns the Session that should be replaced when saving the session, if any.

Currently we invalidate whenever the auth ID has changed (login, logout, different user) in order to prevent session fixation attacks. We also invalidate when asked to via forceInvalidate.

saveSessionOnDb Source #

Arguments

:: forall sto. Storage sto 
=> State sto 
-> UTCTime

Now.

-> Maybe (Session (SessionData sto))

The old session, if any.

-> DecomposedSession (SessionData sto)

The session data to be saved.

-> TransactionM sto (Maybe (Session (SessionData sto)))

Copy of saved session.

Save a session on the database. If an old session is supplied, it is replaced, otherwise a new session is generated. If the session is empty, it is not saved and Nothing is returned. If the timeout resolution optimization is applied (cf. setTimeoutResolution), the old session is returned and no update is made.

forceInvalidateKey :: Text Source #

The session key used to signal that the session ID should be invalidated.

data ForceInvalidate Source #

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 Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Enum ForceInvalidate Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Eq ForceInvalidate Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Ord ForceInvalidate Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Read ForceInvalidate Source # 
Instance details

Defined in Web.ServerSession.Core.Internal

Show ForceInvalidate Source # 
Instance details

Defined in Web.ServerSession.Core.Internal