Safe Haskell | None |
---|---|
Language | Haskell98 |
- data SessionManager
- withSession :: SnapletLens b SessionManager -> Handler b v a -> Handler b v a
- commitSession :: Handler b SessionManager ()
- setInSession :: Text -> Text -> Handler b SessionManager ()
- getFromSession :: Text -> Handler b SessionManager (Maybe Text)
- deleteFromSession :: Text -> Handler b SessionManager ()
- csrfToken :: Handler b SessionManager Text
- sessionToList :: Handler b SessionManager [(Text, Text)]
- resetSession :: Handler b SessionManager ()
- touchSession :: Handler b SessionManager ()
- module Snap.Snaplet.Session.Common
- type SecureCookie t = (UTCTime, t)
- getSecureCookie :: (MonadSnap m, Serialize t) => ByteString -> Key -> Maybe Int -> m (Maybe t)
- setSecureCookie :: (MonadSnap m, Serialize t) => ByteString -> Key -> Maybe Int -> t -> m ()
- checkTimeout :: MonadSnap m => Maybe Int -> UTCTime -> m Bool
Documentation
data SessionManager Source
Any Haskell record that is a member of the ISessionManager
typeclass can be stuffed inside a SessionManager
to enable all
session-related functionality.
To use sessions in your application, just find a Backend that would
produce one for you inside of your Initializer
. See
initCookieSessionManager
in
CookieSession
for a built-in option
that would get you started.
withSession :: SnapletLens b SessionManager -> Handler b v a -> Handler b v a Source
Wrap around a handler, committing any changes in the session at the end
commitSession :: Handler b SessionManager () Source
Commit changes to session within the current request cycle
setInSession :: Text -> Text -> Handler b SessionManager () Source
Set a key-value pair in the current session
getFromSession :: Text -> Handler b SessionManager (Maybe Text) Source
Get a key from the current session
deleteFromSession :: Text -> Handler b SessionManager () Source
Remove a key from the current session
csrfToken :: Handler b SessionManager Text Source
Returns a CSRF Token unique to the current session
sessionToList :: Handler b SessionManager [(Text, Text)] Source
Return session contents as an association list
resetSession :: Handler b SessionManager () Source
Deletes the session cookie, effectively resetting the session
touchSession :: Handler b SessionManager () Source
Touch the session so the timeout gets refreshed
Utilities Exported For Convenience
module Snap.Snaplet.Session.Common
type SecureCookie t = (UTCTime, t) Source
Serialize UTCTime instance Serialize UTCTime where put t = put (round (utcTimeToPOSIXSeconds t) :: Integer) get = posixSecondsToUTCTime . fromInteger $ get
Arbitrary payload with timestamp.