Network.CGI.Session
Description
Example usage:
module Main where import Data.Maybe import Network.CGI import Network.CGI.Session import Network.FastCGI main = do runSessionCGI "myapp" runFastCGI $ do n <- fmap (fromMaybe 0) $ sessionGet "age" sessionIns "age" 1 (+) output $ show n ++ " visits to this page."
- data Session = Session {}
- type Sessions = MVar ([Integer], Map Integer Session)
- type SessionName = String
- type SessionM = StateT Session (CGIT IO)
- makeSessions :: IO Sessions
- initSession :: SessionName -> Sessions -> CGI Session
- updateSession :: Sessions -> Session -> CGI ()
- sessionId :: SessionM Integer
- runSessionCGI :: SessionName -> (CGI CGIResult -> IO ()) -> SessionM CGIResult -> IO ()
- runSession :: Sessions -> SessionM a -> Session -> CGI a
- sessionIns :: (Read a, Show a) => String -> a -> (a -> a -> a) -> SessionM ()
- sessionDel :: String -> SessionM ()
- sessionGet :: Read a => String -> SessionM (Maybe a)
- makeSession :: SessionName -> Sessions -> CGI Session
- getSession :: SessionName -> Sessions -> CGI (Maybe Session)
Types
A session consists of a unique id and a map.
type Sessions = MVar ([Integer], Map Integer Session)Source
Sessions and unique ids are stored in an MVar.
type SessionName = StringSource
The cookie prefix (e.g. MYHASKELLCOOKIE).
type SessionM = StateT Session (CGIT IO)Source
A simple Session monad. Recommend you define your own.
Initialising and querying/updating
makeSessions :: IO SessionsSource
Make the sessions state.
initSession :: SessionName -> Sessions -> CGI SessionSource
Grab the session or create a new one.
A simple Session monad.
runSessionCGI :: SessionName -> (CGI CGIResult -> IO ()) -> SessionM CGIResult -> IO ()Source
Initialise a session state and start a F/CGI process. This is a bit of a pattern so I've included it here for convenience.
sessionIns :: (Read a, Show a) => String -> a -> (a -> a -> a) -> SessionM ()Source
Session value inserter/updater.
sessionDel :: String -> SessionM ()Source
Session value deleter.
Utilities
makeSession :: SessionName -> Sessions -> CGI SessionSource
Create a new session and update the Mvar.
getSession :: SessionName -> Sessions -> CGI (Maybe Session)Source
Try to get the current session.