Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype SessionId sess = S {}
- checkSessionId :: Text -> Maybe (SessionId sess)
- generateSessionId :: Generator -> IO (SessionId sess)
- type AuthId = ByteString
- data Session sess = Session {
- sessionKey :: SessionId sess
- sessionAuthId :: Maybe AuthId
- sessionData :: Decomposed sess
- sessionCreatedAt :: UTCTime
- sessionAccessedAt :: UTCTime
- newtype SessionMap = SessionMap {}
- class (Show (Decomposed sess), Typeable (Decomposed sess), Typeable sess) => IsSessionData sess where
- type Decomposed sess :: *
- emptySession :: sess
- decomposeSession :: Text -> sess -> DecomposedSession sess
- recomposeSession :: Text -> Maybe AuthId -> Decomposed sess -> sess
- isSameDecomposed :: proxy sess -> Decomposed sess -> Decomposed sess -> Bool
- isDecomposedEmpty :: proxy sess -> Decomposed sess -> Bool
- data DecomposedSession sess = DecomposedSession {
- dsAuthId :: !(Maybe ByteString)
- dsForceInvalidate :: !ForceInvalidate
- dsDecomposed :: !(Decomposed sess)
- class (Typeable sto, MonadIO (TransactionM sto), IsSessionData (SessionData sto)) => Storage sto where
- type SessionData sto :: *
- type TransactionM sto :: * -> *
- runTransactionM :: sto -> TransactionM sto a -> IO a
- getSession :: sto -> SessionId (SessionData sto) -> TransactionM sto (Maybe (Session (SessionData sto)))
- deleteSession :: sto -> SessionId (SessionData sto) -> TransactionM sto ()
- deleteAllSessionsOfAuthId :: sto -> AuthId -> TransactionM sto ()
- insertSession :: sto -> Session (SessionData sto) -> TransactionM sto ()
- replaceSession :: sto -> Session (SessionData sto) -> TransactionM sto ()
- data StorageException sto
- = SessionAlreadyExists {
- seExistingSession :: Session (SessionData sto)
- seNewSession :: Session (SessionData sto)
- | SessionDoesNotExist {
- seNewSession :: Session (SessionData sto)
- = SessionAlreadyExists {
- data State sto = State {
- generator :: !Generator
- storage :: !sto
- cookieName :: !Text
- authKey :: !Text
- idleTimeout :: !(Maybe NominalDiffTime)
- absoluteTimeout :: !(Maybe NominalDiffTime)
- timeoutResolution :: !(Maybe NominalDiffTime)
- persistentCookies :: !Bool
- httpOnlyCookies :: !Bool
- secureCookies :: !Bool
- createState :: MonadIO m => sto -> m (State sto)
- setCookieName :: Text -> State sto -> State sto
- setAuthKey :: Text -> State sto -> State sto
- setIdleTimeout :: Maybe NominalDiffTime -> State sto -> State sto
- setAbsoluteTimeout :: Maybe NominalDiffTime -> State sto -> State sto
- setTimeoutResolution :: Maybe NominalDiffTime -> State sto -> State sto
- setPersistentCookies :: Bool -> State sto -> State sto
- setHttpOnlyCookies :: Bool -> State sto -> State sto
- setSecureCookies :: Bool -> State sto -> State sto
- getCookieName :: State sto -> Text
- getHttpOnlyCookies :: State sto -> Bool
- getSecureCookies :: State sto -> Bool
- loadSession :: Storage sto => State sto -> Maybe ByteString -> IO (SessionData sto, SaveSessionToken sto)
- checkExpired :: UTCTime -> State sto -> Session sess -> Maybe (Session sess)
- nextExpires :: State sto -> Session sess -> Maybe UTCTime
- cookieExpires :: State sto -> Session sess -> Maybe UTCTime
- saveSession :: Storage sto => State sto -> SaveSessionToken sto -> SessionData sto -> IO (Maybe (Session (SessionData sto)))
- data SaveSessionToken sto = SaveSessionToken (Maybe (Session (SessionData sto))) UTCTime
- invalidateIfNeeded :: Storage sto => State sto -> Maybe (Session (SessionData sto)) -> DecomposedSession (SessionData sto) -> TransactionM sto (Maybe (Session (SessionData sto)))
- saveSessionOnDb :: forall sto. Storage sto => State sto -> UTCTime -> Maybe (Session (SessionData sto)) -> DecomposedSession (SessionData sto) -> TransactionM sto (Maybe (Session (SessionData sto)))
- forceInvalidateKey :: Text
- data ForceInvalidate
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:
- Use
fromPathPiece
for parsing untrusted input. - Use
generateSessionId
for securely generating new session IDs.
Instances
Eq (SessionId sess) Source # | |
Ord (SessionId sess) Source # | |
Defined in Web.ServerSession.Core.Internal 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 # | |
Read (SessionId sess) Source # | |
Show (SessionId sess) Source # | |
Hashable (SessionId sess) Source # | |
Defined in Web.ServerSession.Core.Internal | |
ToJSON (SessionId sess) Source # | |
Defined in Web.ServerSession.Core.Internal | |
FromJSON (SessionId sess) Source # | |
PathPiece (SessionId sess) Source # | Sanity checks input on |
Defined in Web.ServerSession.Core.Internal 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.
type AuthId = ByteString Source #
Value of the authKey
session key.
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.
Session | |
|
Instances
Eq (Decomposed sess) => Eq (Session sess) Source # | |
Ord (Decomposed sess) => Ord (Session sess) Source # | |
Defined in Web.ServerSession.Core.Internal | |
Show (Decomposed sess) => Show (Session sess) Source # | |
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.
Instances
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
.
type Decomposed sess :: * Source #
The type of the session data after being decomposed. This
may be the same as sess
.
emptySession :: sess Source #
Empty session data.
:: Text | The auth key (cf. |
-> sess | Session data to be decomposed. |
-> DecomposedSession sess | Decomposed session data. |
Decompose session data into:
- The auth ID of the logged in user (cf.
setAuthKey
,dsAuthId
). - If the session is being forced to be invalidated
(cf.
forceInvalidateKey
,ForceInvalidate
). - The rest of the session data (cf.
Decomposed
).
:: Text | The auth key (cf. |
-> Maybe AuthId | The |
-> 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
IsSessionData SessionMap Source # | A |
Defined in Web.ServerSession.Core.Internal type Decomposed SessionMap Source # emptySession :: SessionMap Source # decomposeSession :: Text -> SessionMap -> DecomposedSession SessionMap Source # recomposeSession :: Text -> Maybe AuthId -> Decomposed SessionMap -> SessionMap Source # isSameDecomposed :: proxy SessionMap -> Decomposed SessionMap -> Decomposed SessionMap -> Bool Source # isDecomposedEmpty :: proxy SessionMap -> Decomposed SessionMap -> Bool Source # |
data DecomposedSession sess Source #
A session data type sess
with its special variables taken apart.
DecomposedSession | |
|
Instances
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.
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.
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:
- 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. - 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). - 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.
SessionAlreadyExists | Exception thrown by |
| |
SessionDoesNotExist | Exception thrown by |
|
Instances
The server-side session backend needs to maintain some state in order to work:
- A nonce generator for the session IDs.
- A reference to the storage backend.
- The name of cookie where the session ID will be saved (
setCookieName
). - Authentication session variable (
setAuthKey
). - Idle and absolute timeouts (
setIdleTimeout
andsetAbsoluteTimeout
). - Timeout resolution (
setTimeoutResolution
). - Whether cookies should be persistent
(
setPersistentCookies
), HTTP-only (setHTTPOnlyCookies
) and/or secure (setSecureCookies
).
Create a new State
using createState
.
State | |
|
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
.
getCookieName :: State sto -> Text Source #
Cf. setCookieName
.
getHttpOnlyCookies :: State sto -> Bool Source #
Cf. setHttpOnlyCookies
.
getSecureCookies :: State sto -> Bool Source #
Cf. setSecureCookies
.
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.
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.
SaveSessionToken (Maybe (Session (SessionData sto))) UTCTime |
Instances
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
.
:: 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.
CurrentSessionId | Invalidate the current session ID. The current session
ID is automatically invalidated on login and logout
(cf. |
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 Note that, for the purposes of
|
DoNotForceInvalidate | Do not force invalidate. Invalidate only if automatically. This is the default. |