| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Web.ServerSession.Backend.Redis.Internal
Description
Internal module exposing the guts of the package. Use at your own risk. No API stability guarantees apply.
Synopsis
- data RedisStorage sess = RedisStorage {}
- data RedisStorageException
- = ExpectedTxSuccess (TxResult ())
- | ExpectedRight Reply
- transaction :: RedisTx (Queued ()) -> Redis ()
- unwrap :: Redis (Either Reply a) -> Redis a
- rSessionKey :: SessionId sess -> ByteString
- rAuthKey :: AuthId -> ByteString
- class IsSessionData sess => RedisSession sess where
- toHash :: Proxy sess -> Decomposed sess -> [(ByteString, ByteString)]
- fromHash :: Proxy sess -> [(ByteString, ByteString)] -> Decomposed sess
- parseSession :: forall sess. RedisSession sess => SessionId sess -> [(ByteString, ByteString)] -> Maybe (Session sess)
- printSession :: forall sess. RedisSession sess => Session sess -> [(ByteString, ByteString)]
- parseUTCTime :: ByteString -> UTCTime
- printUTCTime :: UTCTime -> ByteString
- timeFormat :: String
- getSessionImpl :: RedisSession sess => SessionId sess -> Redis (Maybe (Session sess))
- deleteSessionImpl :: RedisSession sess => SessionId sess -> Redis ()
- removeSessionFromAuthId :: (RedisCtx m f, Functor m) => SessionId sess -> Maybe AuthId -> m ()
- insertSessionForAuthId :: (RedisCtx m f, Functor m) => SessionId sess -> Maybe AuthId -> m ()
- deleteAllSessionsOfAuthIdImpl :: AuthId -> Redis ()
- insertSessionImpl :: RedisSession sess => RedisStorage sess -> Session sess -> Redis ()
- replaceSessionImpl :: RedisSession sess => RedisStorage sess -> Session sess -> Redis ()
- throwRS :: Storage (RedisStorage sess) => StorageException (RedisStorage sess) -> Redis a
Documentation
data RedisStorage sess Source #
Session storage backend using Redis via the hedis package.
Constructors
| RedisStorage | |
Fields
| |
Instances
data RedisStorageException Source #
An exception thrown by the serversession-backend-redis
package.
Constructors
| ExpectedTxSuccess (TxResult ()) | We expected |
| ExpectedRight Reply |
Instances
| Show RedisStorageException Source # | |
Defined in Web.ServerSession.Backend.Redis.Internal Methods showsPrec :: Int -> RedisStorageException -> ShowS # show :: RedisStorageException -> String # showList :: [RedisStorageException] -> ShowS # | |
| Exception RedisStorageException Source # | |
Defined in Web.ServerSession.Backend.Redis.Internal | |
transaction :: RedisTx (Queued ()) -> Redis () Source #
Run the given Redis transaction and force its result.
Throws a RedisStorageException if the result is not
TxSuccess.
unwrap :: Redis (Either Reply a) -> Redis a Source #
Unwraps an Either by throwing an exception if
not Reply aRight.
rSessionKey :: SessionId sess -> ByteString Source #
Redis key for the given session ID.
rAuthKey :: AuthId -> ByteString Source #
Redis key for the given auth ID.
class IsSessionData sess => RedisSession sess where Source #
Class for data types that can be used as session data for the Redis backend.
It should hold that
fromHash p . perm . toHash p === id
for all list permutations perm :: [a] -> [a],
where p :: Proxy sess.
Methods
toHash :: Proxy sess -> Decomposed sess -> [(ByteString, ByteString)] Source #
Transform a decomposed session into a Redis hash. Keys
will be prepended with "data:" before being stored.
fromHash :: Proxy sess -> [(ByteString, ByteString)] -> Decomposed sess Source #
Parse back a Redis hash into session data.
Instances
| RedisSession SessionMap Source # | Assumes that keys are UTF-8 encoded when parsing (which is
true if keys are always generated via |
Defined in Web.ServerSession.Backend.Redis.Internal Methods toHash :: Proxy SessionMap -> Decomposed SessionMap -> [(ByteString, ByteString)] Source # fromHash :: Proxy SessionMap -> [(ByteString, ByteString)] -> Decomposed SessionMap Source # | |
parseSession :: forall sess. RedisSession sess => SessionId sess -> [(ByteString, ByteString)] -> Maybe (Session sess) Source #
Parse a Session from a Redis hash.
printSession :: forall sess. RedisSession sess => Session sess -> [(ByteString, ByteString)] Source #
Convert a Session into a Redis hash.
parseUTCTime :: ByteString -> UTCTime Source #
Parse UTCTime from a ByteString stored on Redis. Uses
error on parse error.
printUTCTime :: UTCTime -> ByteString Source #
Convert a UTCTime into a ByteString to be stored on
Redis.
timeFormat :: String Source #
Time format used when storing UTCTime.
getSessionImpl :: RedisSession sess => SessionId sess -> Redis (Maybe (Session sess)) Source #
Get the session for the given session ID.
deleteSessionImpl :: RedisSession sess => SessionId sess -> Redis () Source #
Delete the session with given session ID.
removeSessionFromAuthId :: (RedisCtx m f, Functor m) => SessionId sess -> Maybe AuthId -> m () Source #
insertSessionForAuthId :: (RedisCtx m f, Functor m) => SessionId sess -> Maybe AuthId -> m () Source #
deleteAllSessionsOfAuthIdImpl :: AuthId -> Redis () Source #
Delete all sessions of the given auth ID.
insertSessionImpl :: RedisSession sess => RedisStorage sess -> Session sess -> Redis () Source #
Insert a new session.
replaceSessionImpl :: RedisSession sess => RedisStorage sess -> Session sess -> Redis () Source #
Replace the contents of a session.
throwRS :: Storage (RedisStorage sess) => StorageException (RedisStorage sess) -> Redis a Source #
Specialization of throwIO for RedisStorage.