| Copyright | (c) 2025 Tushar Adhatrao (c) 2025 Marco Zocca |
|---|---|
| License | BSD-3-Clause |
| Maintainer | |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Scotty.Session
Description
This module provides session management functionality for Scotty web applications.
Example usage:
{-# LANGUAGE OverloadedStrings #-}
import Web.Scotty
import Web.Scotty.Session
import Control.Monad.IO.Class (liftIO)
main :: IO ()
main = do
-- Create a session jar
sessionJar <- createSessionJar
scotty 3000 $ do
-- Route to create a session
get "/create" $ do
sess <- createUserSession sessionJar "user data"
html $ "Session created with ID: " <> sessId sess
-- Route to read a session
get "/read" $ do
eSession <- getUserSession sessionJar
case eSession of
Left _-> html "No session found or session expired."
Right sess -> html $ "Session content: " <> sessContent sess
Synopsis
- data Session a = Session {
- sessId :: SessionId
- sessExpiresAt :: UTCTime
- sessContent :: a
- type SessionId = Text
- type SessionJar a = TVar (HashMap SessionId (Session a))
- data SessionStatus
- createSessionJar :: IO (SessionJar a)
- createUserSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> Maybe Int -> a -> ActionT m (Session a)
- createSession :: SessionJar a -> Maybe Int -> a -> IO (Session a)
- readUserSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> ActionT m (Either SessionStatus a)
- readSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> SessionId -> ActionT m (Either SessionStatus a)
- getUserSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> ActionT m (Either SessionStatus (Session a))
- getSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> SessionId -> ActionT m (Either SessionStatus (Session a))
- addSession :: SessionJar a -> Session a -> IO ()
- deleteSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> SessionId -> ActionT m ()
- maintainSessions :: SessionJar a -> IO ()
Documentation
Represents a session containing an ID, expiration time, and content.
Constructors
| Session | |
Fields
| |
type SessionJar a = TVar (HashMap SessionId (Session a)) Source #
Type for session storage, a transactional variable containing a map of session IDs to sessions.
data SessionStatus Source #
Status of a session lookup.
Instances
| Show SessionStatus Source # | |
Defined in Web.Scotty.Session Methods showsPrec :: Int -> SessionStatus -> ShowS # show :: SessionStatus -> String # showList :: [SessionStatus] -> ShowS # | |
| Eq SessionStatus Source # | |
Defined in Web.Scotty.Session Methods (==) :: SessionStatus -> SessionStatus -> Bool # (/=) :: SessionStatus -> SessionStatus -> Bool # | |
Create Session Jar
createSessionJar :: IO (SessionJar a) Source #
Creates a new session jar and starts a background thread to maintain it.
Create session
Arguments
| :: forall (m :: Type -> Type) a. MonadIO m | |
| => SessionJar a | SessionJar, which can be created by createSessionJar |
| -> Maybe Int | Optional expiration time (in seconds) |
| -> a | Content |
| -> ActionT m (Session a) |
Creates a new session for a user, storing the content and setting a cookie.
createSession :: SessionJar a -> Maybe Int -> a -> IO (Session a) Source #
Creates a new session with a generated ID, sets its expiration, | and adds it to the session jar.
Read session
readUserSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> ActionT m (Either SessionStatus a) Source #
Reads the content of the current user's session.
readSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> SessionId -> ActionT m (Either SessionStatus a) Source #
Reads the content of a session by its ID.
getUserSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> ActionT m (Either SessionStatus (Session a)) Source #
Retrieves the current user's session based on the "sess_id" cookie. | Returns `Left SessionStatus` if the session is expired or does not exist.
getSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> SessionId -> ActionT m (Either SessionStatus (Session a)) Source #
Retrieves a session by its ID from the session jar.
Add session
addSession :: SessionJar a -> Session a -> IO () Source #
Adds or overwrites a new session to the session jar.
Delte session
deleteSession :: forall (m :: Type -> Type) a. MonadIO m => SessionJar a -> SessionId -> ActionT m () Source #
Deletes a session by its ID from the session jar.
Helper functions
maintainSessions :: SessionJar a -> IO () Source #
Continuously removes expired sessions from the session jar.