{-| Description: Beam table definition for a generic Spock session Spock likes to store its session RAM, which is mostly great unless you need persistence or multiple machines. This doesn't do anything interesting with Spock's session manager, but just defines enough of a table to be able to store Spock's core session information. -} module TsWeb.Tables.Session where import Data.Text (Text) import Data.Time.Clock (UTCTime) import Database.Beam -- | A generic Beam table to store a Spock session. The '_sessionData' should -- be your useful info, like a logged-in user or whatever. See -- "TsWeb.Tables.Session.Test" for a type-checking but not very function idea -- of what '_sessionData' could look like, or the code under -- 'Example.Main.main' for a fully-functional (but dumb) webapp using all this -- stuff. data SessionT d f = Session { _sessionId :: C f Text -- ^Spock-generated session ID , _sessionCsrf :: C f Text -- ^Session's CSRF token , _sessionExpires :: C f UTCTime -- ^Expiration date for this session , _sessionData :: d f -- ^User-defined session data } deriving (Generic) -- |Concrete session type Session d = SessionT d Identity -- |Session primary key type SessionId d = PrimaryKey (SessionT d) Identity deriving instance Show (PrimaryKey (SessionT d) Identity) deriving instance Show (d Identity) => Show (Session d) deriving instance Eq (PrimaryKey (SessionT d) Identity) deriving instance Eq (d Identity) => Eq (Session d) deriving instance Ord (PrimaryKey (SessionT d) Identity) deriving instance Ord (d Identity) => Ord (Session d) instance Beamable (PrimaryKey (SessionT d)) instance Beamable d => Beamable (SessionT d) instance (Beamable d, Typeable d) => Table (SessionT d) where data PrimaryKey (SessionT d) f = SessionId (Columnar f Text) deriving Generic primaryKey = SessionId . _sessionId