serversession-backend-acid-state-1.0.2: Storage backend for serversession using acid-state.

Safe HaskellNone
LanguageHaskell98

Web.ServerSession.Backend.Acid

Description

Storage backend for serversession using acid-state.

In order to use this backend, just open the AcidState. For example:

import Control.Exception (bracket)
import Data.Acid.Local (openLocalState, createCheckpointAndClose)
import Web.ServerSession.Backend.Acid (AcidStorage(..), emptyState)

withSessionStorage :: (AcidStorage -> IO a) -> IO a
withSessionStorage =
  bracket
    (AcidStorage <$> openLocalState emptyState)
    (createCheckpointAndClose . acidState)

Synopsis

Documentation

newtype AcidStorage sess Source

Session storage backend using acid-state.

Constructors

AcidStorage 

Fields

acidState :: AcidState (ServerSessionAcidState sess)

Open AcidState of server sessions.

Instances

(IsSessionData sess, SafeCopy sess, SafeCopy (Decomposed sess)) => Storage (AcidStorage sess)

We do not provide any ACID guarantees for different actions running inside the same TransactionM AcidStorage.

Typeable (* -> *) AcidStorage 
type TransactionM (AcidStorage sess) = IO 
type SessionData (AcidStorage sess) = sess 

data ServerSessionAcidState sess Source

The current sessions.

Besides the obvious map from session IDs to sessions, we also maintain a map of auth IDs to session IDs. This allow us to quickly invalidate all sessions of a given user.

Instances

AcidContext sess => IsAcidic (ServerSessionAcidState sess) 
SafeCopy (Decomposed sess) => SafeCopy (ServerSessionAcidState sess)

We can't deriveSafeCopy 0 'base ''ServerSessionAcidState due to the required context.

Typeable (* -> *) ServerSessionAcidState