happstack-clientsession-7.3.1: client-side session data

Safe HaskellNone
LanguageHaskell98

Happstack.Server.ClientSession

Contents

Description

This module provides a simple session implementation which stores session data on the client as a cookie value.

The cookie values are stored in an encrypted cookie to make it more difficult for users to tamper with the values. However, this does not prevent replay attacks, and should not be seen as a substitute for using HTTPS. Additionally, the cryptography libraries used to encrypt the cookie have never been audited. Hence you are encouraged to think carefully about what data you put in the session data.

Another important thing to realize is client-side sessions do not provide Isolation. Imagine if the browser makes multiple simultaneous requests, which each modify the session data. The browser will submit the same cookie for each the requests, and each request handling thread will get their own copy of the session data. The threads will then modify their local copies independently and send their modified values back to the browser, overwriting each other. The final value will be determined by which ever request is sent last, and any changes made by the other request will be entirely lost.

This means that clientsessions would not be suitable for implementing a request counter, because if overlapping requests are made, the count will be off. The count will only be accurate if the requests are processed sequentially. That said, the demo code implements a request counter anyway, because it is short and sweet. Also, this caveat was forgotten when the example code was being written.

If you only modify the session data for POST requests, but not GET requests you are less likely to run into situations where you are losing changes, because there are not a lot of cases where a client will be submitting multiple POST requests in parallel. Though there is no guarantee.

Alternatively, you can choose to only store data where it is OK if modifications are lost. For example, if the session data contains only a userid and the time of the last request they made, then there is no great loss if some of the modifications are lost, because the access times are going to all be about the same anyway.

By default the client will need to submit the cookie that contains the client session data for every request (including images, and other static assets). So, storing a large amount of data in the client session will make requests slower and is not recommended. If you have assets which can be served with out examining the client session data you can use the sessionPath and sessionDomain parameters of SessionConf to limit when the browser sends the session data cookie.

The first thing you need to do is enable some extensions which can be done via a LANGUAGE pragma at the top of your app:

{-# LANGUAGE DeriveDataTypeable, TemplateHaskell #-}

Then you will need some imports:

module Main where

import Happstack.Server   (ServerPartT, Response, simpleHTTP
                         , nullConf, nullDir, ok, toResponse
                         )
import Happstack.Server.ClientSession
                          ( ClientSession(..), ClientSessionT(..)
                         , getDefaultKey, mkSessionConf
                         , liftSessionStateT, withClientSessionT
                         )
import Data.Data          (Data, Typeable)
import Data.Lens          ((+=))
import Data.Lens.Template (makeLens)
import Data.SafeCopy      (base, deriveSafeCopy)

Next you will want to create a type to hold your session data. Here we use a simple record which we will update using data-lens-fd. But, you could also store a, Map Text Text, or whatever suits your fancy as long as it can be serialized. (So no data types that include functions, existential types, etc).

data SessionData = SessionData
    { _count    :: Integer
    }
   deriving (Eq, Ord, Read, Show, Data, Typeable)

-- | here we make it a lens, but that is not required
$(makeLens ''SessionData)

We use the safecopy library to serialize the data so we can encrypt it and store it in a cookie. safecopy provides version migration, which means that we will be able to read-in old session data if we change the data type. The easiest way to create a SafeCopy instance is with deriveSafeCopy:

$(deriveSafeCopy 0 'base ''SessionData)

We also need to define what an emptySession looks like. This will be used for creating new sessions when the client does not already have one:

instance ClientSession SessionData where
    emptySession = SessionData { _count = 0 }

Next we have a function which reads a client-specific page counter and returns the number of times the page has been reloaded.

In this function we use, liftSessionStateT to lift the += lens function into ClientSessionT to increment and return the value stored in the client session.

Alternatively, we could have used the getSession and putSession functions from MonadClientSession. Those functions do not require the use of liftSessionStateT.

routes :: ClientSessionT SessionData (ServerPartT IO) Response
routes =
    do nullDir
       c <- liftSessionStateT $ count += 1
       ok $ toResponse $ "you have viewed this page " ++ (show c) ++ " time(s)."

Finally, we unwrap the ClientSessionT monad transformer using withClientSessionT.

The SessionConf type requires an encryption key. You can generate the key using getDefaultKey uses a default filename. Alternatively, you can specific the name you want to use explicitly using getKey. The key will be created automatically if it does not already exist.

If you change the key, all existing client sessions will be invalidated.

main :: IO ()
main =
    do key <- getDefaultKey
       let sessionConf = mkSessionConf key
       simpleHTTP nullConf $ withClientSessionT sessionConf $ routes

In a real application you might want to use a newtype wrapper around ClientSessionT to keep your type signatures sane. An alternative version of this demo which does that can be found here:

http://patch-tag.com/r/mae/happstack/snapshot/current/content/pretty/happstack-clientsession/demo/demo.hs

Synopsis

Happstack.Server.ClientSession

class SafeCopy st => ClientSession st where Source #

Your session type must have an instance for this class.

Minimal complete definition

emptySession

Methods

emptySession :: st Source #

An empty session, i.e. what you get when there is no existing session stored.

data SessionStatus sessionData Source #

Wrapper around the sessionData which tracks it state so we can avoid decoding or encoding/sending the cookie when not required

Constructors

Unread 
NoChange sessionData 
Modified sessionData 
Expired 

Instances

Eq sessionData => Eq (SessionStatus sessionData) Source # 

Methods

(==) :: SessionStatus sessionData -> SessionStatus sessionData -> Bool #

(/=) :: SessionStatus sessionData -> SessionStatus sessionData -> Bool #

Ord sessionData => Ord (SessionStatus sessionData) Source # 

Methods

compare :: SessionStatus sessionData -> SessionStatus sessionData -> Ordering #

(<) :: SessionStatus sessionData -> SessionStatus sessionData -> Bool #

(<=) :: SessionStatus sessionData -> SessionStatus sessionData -> Bool #

(>) :: SessionStatus sessionData -> SessionStatus sessionData -> Bool #

(>=) :: SessionStatus sessionData -> SessionStatus sessionData -> Bool #

max :: SessionStatus sessionData -> SessionStatus sessionData -> SessionStatus sessionData #

min :: SessionStatus sessionData -> SessionStatus sessionData -> SessionStatus sessionData #

Read sessionData => Read (SessionStatus sessionData) Source # 

Methods

readsPrec :: Int -> ReadS (SessionStatus sessionData) #

readList :: ReadS [SessionStatus sessionData] #

readPrec :: ReadPrec (SessionStatus sessionData) #

readListPrec :: ReadPrec [SessionStatus sessionData] #

Show sessionData => Show (SessionStatus sessionData) Source # 

Methods

showsPrec :: Int -> SessionStatus sessionData -> ShowS #

show :: SessionStatus sessionData -> String #

showList :: [SessionStatus sessionData] -> ShowS #

class MonadClientSession sessionData m | m -> sessionData where Source #

MonadClientSession provides the primary interface to get sessionData, put sessionData or expire sessionData.

This is a class so you can use newtype deriving to make the functions available in your custom server monad.

Minimal complete definition

getSession, putSession, expireSession

Methods

getSession :: m sessionData Source #

putSession :: sessionData -> m () Source #

expireSession :: m () Source #

Instances

(Monad m, MonadClientSession sessionData m, Monoid w) => MonadClientSession sessionData (WriterT w m) Source # 

Methods

getSession :: WriterT w m sessionData Source #

putSession :: sessionData -> WriterT w m () Source #

expireSession :: WriterT w m () Source #

(Monad m, MonadClientSession sessionData m) => MonadClientSession sessionData (StateT s m) Source # 

Methods

getSession :: StateT s m sessionData Source #

putSession :: sessionData -> StateT s m () Source #

expireSession :: StateT s m () Source #

(Monad m, MonadClientSession sessionData m, Error e) => MonadClientSession sessionData (ErrorT e m) Source # 

Methods

getSession :: ErrorT e m sessionData Source #

putSession :: sessionData -> ErrorT e m () Source #

expireSession :: ErrorT e m () Source #

(Functor m, MonadPlus m, HasRqData m, ClientSession sessionData) => MonadClientSession sessionData (ClientSessionT sessionData m) Source # 

Methods

getSession :: ClientSessionT sessionData m sessionData Source #

putSession :: sessionData -> ClientSessionT sessionData m () Source #

expireSession :: ClientSessionT sessionData m () Source #

(Monad m, MonadClientSession sessionData m) => MonadClientSession sessionData (ReaderT * r m) Source # 

Methods

getSession :: ReaderT * r m sessionData Source #

putSession :: sessionData -> ReaderT * r m () Source #

expireSession :: ReaderT * r m () Source #

(Monad m, MonadClientSession sessionData m) => MonadClientSession sessionData (ContT * c m) Source # 

Methods

getSession :: ContT * c m sessionData Source #

putSession :: sessionData -> ContT * c m () Source #

expireSession :: ContT * c m () Source #

(Monad m, MonadClientSession sessionData m, Monoid w) => MonadClientSession sessionData (RWST r w s m) Source # 

Methods

getSession :: RWST r w s m sessionData Source #

putSession :: sessionData -> RWST r w s m () Source #

expireSession :: RWST r w s m () Source #

data SessionConf Source #

Configuration for the session cookie for passing to runClientSessionT or withClientSessionT.

Constructors

SessionConf 

Fields

mkSessionConf :: Key -> SessionConf Source #

Create a SessionConf using defaults for everything except sessionKey. You can use record update syntax to override individual fields.

main = do key <- getDefaultKey
          let sessConf = (mkSessionConf key) { sessionCookieLife = oneWeek }
          simpleHTTP nullConf $ withClientSessionT sessConf handlers
  where
    oneWeek  = MaxAge $ 60 * 60 * 24 * 7
    handlers = msum [...]

mkSessionConf is currently defined as:

mkSessionConf :: Key -> SessionConf
mkSessionConf key = SessionConf
   { sessionCookieName = "Happstack.ClientSession"
   , sessionCookieLife = Session
   , sessionKey        = key
   , sessionDomain     = ""
   , sessionPath       = "/"
   , sessionSecure     = False
   , sessionHttpOnly   = True
   }

see also: getKey, getDefaultKey

newtype ClientSessionT sessionData m a Source #

ClientSessionT provides an environment in which we can access and update the client-side session state

The inner monad needs to provide an instance of Happstack so that the cookie value can be read and set. According ClientSessionT must appear outside ServerPartT not inside it.

Constructors

ClientSessionT 

Fields

Instances

MonadRWS r w s m => MonadRWS r w s (ClientSessionT sessionData m) Source # 
MonadReader r m => MonadReader r (ClientSessionT sessionData m) Source # 

Methods

ask :: ClientSessionT sessionData m r #

local :: (r -> r) -> ClientSessionT sessionData m a -> ClientSessionT sessionData m a #

reader :: (r -> a) -> ClientSessionT sessionData m a #

FilterMonad r m => FilterMonad r (ClientSessionT sessionData m) Source # 

Methods

setFilter :: (r -> r) -> ClientSessionT sessionData m () #

composeFilter :: (r -> r) -> ClientSessionT sessionData m () #

getFilter :: ClientSessionT sessionData m b -> ClientSessionT sessionData m (b, r -> r) #

WebMonad r m => WebMonad r (ClientSessionT sessionData m) Source # 

Methods

finishWith :: r -> ClientSessionT sessionData m b #

MonadBase b m => MonadBase b (ClientSessionT sessionData m) Source # 

Methods

liftBase :: b α -> ClientSessionT sessionData m α #

MonadBaseControl b m => MonadBaseControl b (ClientSessionT s m) Source # 

Associated Types

type StM (ClientSessionT s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ClientSessionT s m) b -> b a) -> ClientSessionT s m a #

restoreM :: StM (ClientSessionT s m) a -> ClientSessionT s m a #

MonadError e m => MonadError e (ClientSessionT sessionData m) Source # 

Methods

throwError :: e -> ClientSessionT sessionData m a #

catchError :: ClientSessionT sessionData m a -> (e -> ClientSessionT sessionData m a) -> ClientSessionT sessionData m a #

MonadState s m => MonadState s (ClientSessionT sessionData m) Source # 

Methods

get :: ClientSessionT sessionData m s #

put :: s -> ClientSessionT sessionData m () #

state :: (s -> (a, s)) -> ClientSessionT sessionData m a #

MonadWriter w m => MonadWriter w (ClientSessionT sessionData m) Source # 

Methods

writer :: (a, w) -> ClientSessionT sessionData m a #

tell :: w -> ClientSessionT sessionData m () #

listen :: ClientSessionT sessionData m a -> ClientSessionT sessionData m (a, w) #

pass :: ClientSessionT sessionData m (a, w -> w) -> ClientSessionT sessionData m a #

(Functor m, MonadPlus m, HasRqData m, ClientSession sessionData) => MonadClientSession sessionData (ClientSessionT sessionData m) Source # 

Methods

getSession :: ClientSessionT sessionData m sessionData Source #

putSession :: sessionData -> ClientSessionT sessionData m () Source #

expireSession :: ClientSessionT sessionData m () Source #

MonadTrans (ClientSessionT sessionData) Source # 

Methods

lift :: Monad m => m a -> ClientSessionT sessionData m a #

MonadTransControl (ClientSessionT s) Source # 

Associated Types

type StT (ClientSessionT s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ClientSessionT s) -> m a) -> ClientSessionT s m a #

restoreT :: Monad m => m (StT (ClientSessionT s) a) -> ClientSessionT s m a #

Monad m => Monad (ClientSessionT sessionData m) Source # 

Methods

(>>=) :: ClientSessionT sessionData m a -> (a -> ClientSessionT sessionData m b) -> ClientSessionT sessionData m b #

(>>) :: ClientSessionT sessionData m a -> ClientSessionT sessionData m b -> ClientSessionT sessionData m b #

return :: a -> ClientSessionT sessionData m a #

fail :: String -> ClientSessionT sessionData m a #

Functor m => Functor (ClientSessionT sessionData m) Source # 

Methods

fmap :: (a -> b) -> ClientSessionT sessionData m a -> ClientSessionT sessionData m b #

(<$) :: a -> ClientSessionT sessionData m b -> ClientSessionT sessionData m a #

MonadFix m => MonadFix (ClientSessionT sessionData m) Source # 

Methods

mfix :: (a -> ClientSessionT sessionData m a) -> ClientSessionT sessionData m a #

Monad m => Applicative (ClientSessionT sessionData m) Source # 

Methods

pure :: a -> ClientSessionT sessionData m a #

(<*>) :: ClientSessionT sessionData m (a -> b) -> ClientSessionT sessionData m a -> ClientSessionT sessionData m b #

(*>) :: ClientSessionT sessionData m a -> ClientSessionT sessionData m b -> ClientSessionT sessionData m b #

(<*) :: ClientSessionT sessionData m a -> ClientSessionT sessionData m b -> ClientSessionT sessionData m a #

MonadIO m => MonadIO (ClientSessionT sessionData m) Source # 

Methods

liftIO :: IO a -> ClientSessionT sessionData m a #

MonadPlus m => Alternative (ClientSessionT sessionData m) Source # 

Methods

empty :: ClientSessionT sessionData m a #

(<|>) :: ClientSessionT sessionData m a -> ClientSessionT sessionData m a -> ClientSessionT sessionData m a #

some :: ClientSessionT sessionData m a -> ClientSessionT sessionData m [a] #

many :: ClientSessionT sessionData m a -> ClientSessionT sessionData m [a] #

MonadPlus m => MonadPlus (ClientSessionT sessionData m) Source # 

Methods

mzero :: ClientSessionT sessionData m a #

mplus :: ClientSessionT sessionData m a -> ClientSessionT sessionData m a -> ClientSessionT sessionData m a #

Happstack m => Happstack (ClientSessionT sessionData m) Source # 
(HasRqData m, Monad m) => HasRqData (ClientSessionT sessionData m) Source # 

Methods

askRqEnv :: ClientSessionT sessionData m RqEnv #

localRqEnv :: (RqEnv -> RqEnv) -> ClientSessionT sessionData m a -> ClientSessionT sessionData m a #

rqDataError :: Errors String -> ClientSessionT sessionData m a #

ServerMonad m => ServerMonad (ClientSessionT sessionData m) Source # 

Methods

askRq :: ClientSessionT sessionData m Request #

localRq :: (Request -> Request) -> ClientSessionT sessionData m a -> ClientSessionT sessionData m a #

MonadCont m => MonadCont (ClientSessionT sessionData m) Source # 

Methods

callCC :: ((a -> ClientSessionT sessionData m b) -> ClientSessionT sessionData m a) -> ClientSessionT sessionData m a #

MonadPlus m => Monoid (ClientSessionT sessionData m a) Source # 

Methods

mempty :: ClientSessionT sessionData m a #

mappend :: ClientSessionT sessionData m a -> ClientSessionT sessionData m a -> ClientSessionT sessionData m a #

mconcat :: [ClientSessionT sessionData m a] -> ClientSessionT sessionData m a #

type StT (ClientSessionT s) a Source # 
type StM (ClientSessionT s m) a Source # 

mapClientSessionT :: (forall s. m (a, s) -> n (b, s)) -> ClientSessionT sessionData m a -> ClientSessionT sessionData n b Source #

transform the inner monad, but leave the session data alone.

runClientSessionT :: ClientSessionT sessionData m a -> SessionConf -> m (a, SessionStatus sessionData) Source #

run the ClientSessionT monad and get the result plus the final SessionStatus sessionData

This function does not automatically update the cookie if the session has been modified. It is up to you to do that. You probably want to use withClientSessionT instead.

see also: withClientSessionT, mkSessionConf

withClientSessionT :: (Happstack m, Functor m, Monad m, FilterMonad Response m, ClientSession sessionData) => SessionConf -> ClientSessionT sessionData m a -> m a Source #

Wrapper around your handlers that use the session.

This function automatically takes care of expiring or updating the cookie if the expireSession or modifySession is called.

If no changes are made to the session, then the cookie will not be resent (because there is no need to).

data SessionStateT s m a Source #

SessionStateT is like StateT, except it records if put was ever called

Instances

FilterMonad r m => FilterMonad r (SessionStateT s m) Source # 

Methods

setFilter :: (r -> r) -> SessionStateT s m () #

composeFilter :: (r -> r) -> SessionStateT s m () #

getFilter :: SessionStateT s m b -> SessionStateT s m (b, r -> r) #

WebMonad r m => WebMonad r (SessionStateT s m) Source # 

Methods

finishWith :: r -> SessionStateT s m b #

MonadBase b m => MonadBase b (SessionStateT s m) Source # 

Methods

liftBase :: b α -> SessionStateT s m α #

MonadBaseControl b m => MonadBaseControl b (SessionStateT s m) Source # 

Associated Types

type StM (SessionStateT s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (SessionStateT s m) b -> b a) -> SessionStateT s m a #

restoreM :: StM (SessionStateT s m) a -> SessionStateT s m a #

MonadError e m => MonadError e (SessionStateT s m) Source # 

Methods

throwError :: e -> SessionStateT s m a #

catchError :: SessionStateT s m a -> (e -> SessionStateT s m a) -> SessionStateT s m a #

(Monad m, ClientSession sessionData) => MonadState sessionData (SessionStateT sessionData m) Source # 

Methods

get :: SessionStateT sessionData m sessionData #

put :: sessionData -> SessionStateT sessionData m () #

state :: (sessionData -> (a, sessionData)) -> SessionStateT sessionData m a #

MonadTrans (SessionStateT s) Source # 

Methods

lift :: Monad m => m a -> SessionStateT s m a #

MonadTransControl (SessionStateT s) Source # 

Associated Types

type StT (SessionStateT s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (SessionStateT s) -> m a) -> SessionStateT s m a #

restoreT :: Monad m => m (StT (SessionStateT s) a) -> SessionStateT s m a #

Monad m => Monad (SessionStateT s m) Source # 

Methods

(>>=) :: SessionStateT s m a -> (a -> SessionStateT s m b) -> SessionStateT s m b #

(>>) :: SessionStateT s m a -> SessionStateT s m b -> SessionStateT s m b #

return :: a -> SessionStateT s m a #

fail :: String -> SessionStateT s m a #

Functor m => Functor (SessionStateT s m) Source # 

Methods

fmap :: (a -> b) -> SessionStateT s m a -> SessionStateT s m b #

(<$) :: a -> SessionStateT s m b -> SessionStateT s m a #

MonadFix m => MonadFix (SessionStateT s m) Source # 

Methods

mfix :: (a -> SessionStateT s m a) -> SessionStateT s m a #

Monad m => Applicative (SessionStateT s m) Source # 

Methods

pure :: a -> SessionStateT s m a #

(<*>) :: SessionStateT s m (a -> b) -> SessionStateT s m a -> SessionStateT s m b #

(*>) :: SessionStateT s m a -> SessionStateT s m b -> SessionStateT s m b #

(<*) :: SessionStateT s m a -> SessionStateT s m b -> SessionStateT s m a #

MonadIO m => MonadIO (SessionStateT s m) Source # 

Methods

liftIO :: IO a -> SessionStateT s m a #

MonadPlus m => Alternative (SessionStateT s m) Source # 

Methods

empty :: SessionStateT s m a #

(<|>) :: SessionStateT s m a -> SessionStateT s m a -> SessionStateT s m a #

some :: SessionStateT s m a -> SessionStateT s m [a] #

many :: SessionStateT s m a -> SessionStateT s m [a] #

MonadPlus m => MonadPlus (SessionStateT s m) Source # 

Methods

mzero :: SessionStateT s m a #

mplus :: SessionStateT s m a -> SessionStateT s m a -> SessionStateT s m a #

Happstack m => Happstack (SessionStateT sessionData m) Source # 
(HasRqData m, Monad m) => HasRqData (SessionStateT s m) Source # 
ServerMonad m => ServerMonad (SessionStateT s m) Source # 
MonadCont m => MonadCont (SessionStateT s m) Source # 

Methods

callCC :: ((a -> SessionStateT s m b) -> SessionStateT s m a) -> SessionStateT s m a #

MonadPlus m => Monoid (SessionStateT sessionData m a) Source # 

Methods

mempty :: SessionStateT sessionData m a #

mappend :: SessionStateT sessionData m a -> SessionStateT sessionData m a -> SessionStateT sessionData m a #

mconcat :: [SessionStateT sessionData m a] -> SessionStateT sessionData m a #

type StT (SessionStateT s) a Source # 
type StM (SessionStateT s m) a Source # 
type StM (SessionStateT s m) a = ComposeSt (SessionStateT s) m a

mapSessionStateT :: (forall s. m (a, s) -> n (b, s)) -> SessionStateT sessionData m a -> SessionStateT sessionData n b Source #

Transform the inner monad. (similar to mapStateT)

The forall s. is to prevent you from modifying the session state.

In theory we want this function to have the type:

mapSessionStateT :: (m a -> n b) -> SessionStateT s m a -> SessionStateT s n b

But that can not be done, so this is the next best thing.

liftSessionStateT :: (Monad m, MonadTrans t, MonadClientSession sessionData (t m), Monad (t m)) => SessionStateT sessionData m a -> t m a Source #

lift a computation from the SessionStateT monad

The primary purpose of this function is to make it possible to use the MonadState functions such as get and set to get and set the current session data.

That makes it possible to use the MonadState based functions provided by Lens, e.g.:

do c <- liftSessionStateT $ count += 1

Exported from Web.ClientSession

data Key :: * #

The keys used to store the cookies. We have an AES key used to encrypt the cookie and a Skein-MAC-512-256 key used verify the authencity and integrity of the cookie. The AES key must have exactly 32 bytes (256 bits) while Skein-MAC-512-256 must have 64 bytes (512 bits).

See also getDefaultKey and initKey.

Instances

Eq Key 

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Show Key

Dummy Show instance.

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Serialize Key 

Methods

put :: Putter Key #

get :: Get Key #

getKey #

Arguments

:: FilePath

File name where key is stored.

-> IO Key

The actual key.

Get a key from the given text file.

If the file does not exist or is corrupted a random key will be generated and stored in that file.

randomKey :: IO (ByteString, Key) #

Generate a random Key. Besides the Key, the ByteString passed to initKey is returned so that it can be saved for later use.

Orphan instances