yesod-session-persist-0.0.0.2: SQL session backend for Yesod
Safe HaskellSafe-Inferred
LanguageGHC2021

Yesod.Session.Persist

Synopsis

Setup

makeSessionBackend :: SessionConfiguration persistentBackend persistentRecord -> IO SessionBackend #

Use this to implement makeSessionBackend.

The session type parameter represents the Persistent entity you're using to store sessions (see the SessionPersistence field of the configuration).

data SessionConfiguration persistentBackend persistentRecord #

Constructors

SessionConfiguration 

Fields

Options

data Options (tx :: Type -> Type) (m :: Type -> Type) #

Settings that have defaults

See defaultOptions.

Constructors

Options 

Fields

defaultOptions :: Options IO IO #

Default options

hoistOptions :: Functor m2 => (forall a. tx1 a -> tx2 a) -> (forall a. m1 a -> m2 a) -> Options tx1 m1 -> Options tx2 m2 #

Timing

data TimingOptions a #

Time duration settings

See defaultTimingOptions.

Constructors

TimingOptions 

Fields

  • timeout :: Timeout a

    How long sessions are allowed to live

  • resolution :: Maybe a

    If Just resolution, this setting provides an optimization that can prevent excessive database writes. If the only thing that needs to be updated is the session's last access time, the write will be skipped if the previously recorded access time is within resolution long ago.

Instances

Instances details
Show a => Show (TimingOptions a) 
Instance details

Defined in Session.Timing.Options

Eq a => Eq (TimingOptions a) 
Instance details

Defined in Session.Timing.Options

defaultTimingOptions :: TimingOptions NominalDiffTime #

Default timing options

Timeout

data Timeout a #

How long sessions are allowed to live

See defaultTimeout.

Constructors

Timeout 

Fields

  • idle :: Maybe a

    The amount of time a session will remain active in case there is no activity in the session

    This is used both on the client side (by setting the cookie expires fields) and on the server.

    Setting to Nothing removes the idle timeout.

  • absolute :: Maybe a

    The maximum amount of time a session can be active

    This is used both on the client side (by setting the cookie expires fields) and on the server side.

    Setting to Nothing removes the absolute timeout.

Instances

Instances details
Functor Timeout 
Instance details

Defined in Session.Timing.Timeout

Methods

fmap :: (a -> b) -> Timeout a -> Timeout b #

(<$) :: a -> Timeout b -> Timeout a #

Arbitrary a => Arbitrary (Timeout a) 
Instance details

Defined in Session.Timing.Timeout

Methods

arbitrary :: Gen (Timeout a) #

shrink :: Timeout a -> [Timeout a] #

Generic (Timeout a) 
Instance details

Defined in Session.Timing.Timeout

Associated Types

type Rep (Timeout a) :: Type -> Type #

Methods

from :: Timeout a -> Rep (Timeout a) x #

to :: Rep (Timeout a) x -> Timeout a #

Show a => Show (Timeout a) 
Instance details

Defined in Session.Timing.Timeout

Methods

showsPrec :: Int -> Timeout a -> ShowS #

show :: Timeout a -> String #

showList :: [Timeout a] -> ShowS #

Eq a => Eq (Timeout a) 
Instance details

Defined in Session.Timing.Timeout

Methods

(==) :: Timeout a -> Timeout a -> Bool #

(/=) :: Timeout a -> Timeout a -> Bool #

type Rep (Timeout a) 
Instance details

Defined in Session.Timing.Timeout

type Rep (Timeout a) = D1 ('MetaData "Timeout" "Session.Timing.Timeout" "yesod-session-persist-0.0.0.2-4wroKzVSNpLxsAaD7x2SU-internal" 'False) (C1 ('MetaCons "Timeout" 'PrefixI 'True) (S1 ('MetaSel ('Just "idle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a)) :*: S1 ('MetaSel ('Just "absolute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

defaultTimeout :: Timeout NominalDiffTime #

Default timeouts

  • idle = 8 hours
  • absolute = 30 days

Transport security

data TransportSecurity #

Constructors

RequireSecureTransport

Only allow cookies on HTTPS connections

Set this in production.

AllowPlaintextTranport

Allow cookies over either HTTP or HTTPS

This is okay for development.

Session data model

data Session #

What a saved session looks like in the database

Constructors

Session 

Fields

Instances

Instances details
Show Session 
Instance details

Defined in Yesod.Session.SessionType

Eq Session 
Instance details

Defined in Yesod.Session.SessionType

Methods

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

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

newtype SessionKey #

Secret value that is sent to and subsequently furnished by the client to identify the session

Constructors

SessionKey 

Fields

Instances

Instances details
Show SessionKey 
Instance details

Defined in Session.Key

Eq SessionKey 
Instance details

Defined in Session.Key

Ord SessionKey 
Instance details

Defined in Session.Key

data Time a #

Creation and access times, used to determine session expiration

Constructors

Time 

Fields

  • created :: a

    When the session was created

    This is used to apply the absolute timeout.

  • accessed :: a

    When the session was last accessed

    This is used to apply the idle timeout.

Instances

Instances details
Show a => Show (Time a) 
Instance details

Defined in Session.Timing.Time

Methods

showsPrec :: Int -> Time a -> ShowS #

show :: Time a -> String #

showList :: [Time a] -> ShowS #

Eq a => Eq (Time a) 
Instance details

Defined in Session.Timing.Time

Methods

(==) :: Time a -> Time a -> Bool #

(/=) :: Time a -> Time a -> Bool #

Randomization

newtype Randomization (m :: Type -> Type) #

General means of obtaining randomness

Constructors

Randomization 

Fields

defaultRandomization :: IO (Randomization IO) #

Cryptographically secure deterministic randomization seeded from system entropy using ChaChaDRG from the crypton package

deterministicallyRandom :: DeterministicRandomization -> IO (Randomization IO) #

Convert from a deterministic generator to an effectful one

newtype DeterministicRandomization #

A deterministic random generator

Constructors

DeterministicRandomization 

Fields

Storage

data SessionPersistence backend record (m :: Type -> Type) #

Mapping between Session and a Persistent entity of your choice

Constructors

(PersistRecordBackend record backend, PersistStoreWrite backend, SafeToInsert record) => SessionPersistence 

Fields

data StorageException #

Common exceptions that may be thrown by any storage.

Constructors

SessionAlreadyExists

Thrown when attempting to insert a new session and another session with the same key already exists

SessionDoesNotExist

Thrown when attempting to replace an existing session but no session with the same key exists

Key rotation

assignSessionKeyRotation #

Arguments

:: (MonadHandler m, HasSessionEmbeddings (HandlerSite m)) 
=> Maybe KeyRotation

Just to rotate, or Nothing to cancel any previous request for rotation and restore the default behavior

-> m () 

Indicate whether the current session key should be rotated

The key rotation does not occur immediately; this action only places a value into the session map.

Later calls to assignSessionKeyRotation on the same handler will override earlier calls.

At the end of the request handler, if the value is Just, the session key will be rotated.

The session variable set by this function is then discarded and is not persisted across requests.

data KeyRotation #

Key rotation means we delete the session on the server and copy the stored data into a new session with a different key.

Constructors

RotateSessionKey

Generate a new session key and invalidate the old one

Instances

Instances details
Bounded KeyRotation 
Instance details

Defined in Session.KeyRotation

Enum KeyRotation 
Instance details

Defined in Session.KeyRotation

Read KeyRotation 
Instance details

Defined in Session.KeyRotation

Show KeyRotation 
Instance details

Defined in Session.KeyRotation

Eq KeyRotation 
Instance details

Defined in Session.KeyRotation

Ord KeyRotation 
Instance details

Defined in Session.KeyRotation

Freezing

assignSessionFreeze #

Arguments

:: (MonadHandler m, HasSessionEmbeddings (HandlerSite m)) 
=> Maybe SessionFreeze

Just to freeze the session, or Nothing to cancel any previous request for session freezing and restore the default behavior

-> m () 

Indicate whether the session should be frozen for the handling of the current request

At the end of the request handler, if the value is Just, no database actions will be performed and no cookies will be set.

data SessionFreeze #

Instances

Instances details
Bounded SessionFreeze 
Instance details

Defined in Session.Freeze

Enum SessionFreeze 
Instance details

Defined in Session.Freeze

Read SessionFreeze 
Instance details

Defined in Session.Freeze

Show SessionFreeze 
Instance details

Defined in Session.Freeze

Eq SessionFreeze 
Instance details

Defined in Session.Freeze

Ord SessionFreeze 
Instance details

Defined in Session.Freeze

Session map embedding

data SessionEmbeddings #

Constructors

SessionEmbeddings 

Fields

data Embedding (con :: (Type -> Type) -> Constraint) e a #

Targets a value that is optionally present in some stateful monadic context

Constructors

Embedding 

Fields

type SessionMapEmbedding a = Embedding (MapOperations Text ByteString) () a #

Specifies how we represent some value within a SessionMap

We use this to sort of abuse the session; key rotation and freezing are done by embedding special values among the session data. These special values are extracted from the map before persisting to storage and are never actually saved.

class (Monad m, Ord k) => MapOperations k v (m :: Type -> Type) | m -> k v where #

A monadic context with operations over some Map-like state

This allows us to generalize between pure operations over Map and the more limited session manipulation utilities afforded by Yesod. (See the instance list for this class.)

Methods

lookup :: k -> m (Maybe v) #

assign :: k -> Maybe v -> m () #

Instances

Instances details
MapOperations Text ByteString (HandlerFor site) 
Instance details

Defined in Yesod.Session.Embedding.Map

(Monad m, Ord k) => MapOperations k v (StateT (Map k v) m) 
Instance details

Defined in Yesod.Session.Embedding.Map

Methods

lookup :: k -> StateT (Map k v) m (Maybe v) #

assign :: k -> Maybe v -> StateT (Map k v) m () #

bsKeyEmbedding :: k -> Embedding (MapOperations k a) e a #

An embedding which stores a value at some particular key in a map-like structure

dimapEmbedding :: forall a e b (con :: (Type -> Type) -> Constraint). (a -> Either e b) -> (b -> a) -> Embedding con e a -> Embedding con e b #

showReadKeyEmbedding :: (Read a, Show a) => k -> Embedding (MapOperations k ByteString) () a #

Represents a value in a SessionMap by storing the UTF-8 encoding of its show representation at the given key

Comparison

data Comparison a #

Constructors

Comparison 

Fields

differsOn :: Eq b => (a -> b) -> Comparison a -> Bool #