serversession-backend-persistent-2.0.1: Storage backend for serversession using persistent and an RDBMS.
Safe HaskellNone
LanguageHaskell2010

Web.ServerSession.Backend.Persistent

Description

Storage backend for serversession using persistent.

In order to use this backend, you have to include serverSessionDefs on your migration code. For example, the Yesod scaffold usually includes the following code:

-- On Model.hs
share [mkPersist sqlSettings, mkMigrate "migrateAll"]

-- On Application.hs
makeFoundation =
    ...
    runLoggingT (runSqlPool (runMigration migrateAll) pool) logFunc
    ...

You should changed those lines to:

-- On Model.hs
share [mkPersist sqlSettings, mkSave "entityDefs"]

-- On Application.hs
import Web.ServerSession.Backend.Persistent

mkMigrate "migrateAll" (entityDefs `embedEntityDefs` serverSessionDefsBySessionMap)

makeFoundation =
    ...
    runLoggingT (runSqlPool (runMigration migrateAll) pool) logFunc
    ...

If you're not using SessionMap, just use mkServerSessionDefs and change Proxy type above.

If you forget to setup the migration above, this session storage backend will fail at runtime as the required table will not exist.

Synopsis

Documentation

newtype SqlStorage sess Source #

SQL session storage backend using persistent.

Constructors

SqlStorage 

Fields

data PersistentSession sess Source #

Entity corresponding to a Session.

We're bending persistent in ways it wasn't expected to. In particular, this entity is parametrized over the session type.

Constructors

PersistentSession 

Fields

Instances

Instances details
Eq (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Eq (Decomposed sess) => Eq (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Ord (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Ord (Decomposed sess) => Ord (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Read (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Show (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Show (Decomposed sess) => Show (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

ToJSON (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

(ToJSON (Decomposed sess), PersistFieldSql (Decomposed sess)) => ToJSON (Entity (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

ToJSON (Decomposed sess) => ToJSON (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

FromJSON (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

(FromJSON (Decomposed sess), PersistFieldSql (Decomposed sess)) => FromJSON (Entity (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

FromJSON (Decomposed sess) => FromJSON (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

PathPiece (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

PersistFieldSql (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Methods

sqlType :: Proxy (Key (PersistentSession sess)) -> SqlType #

PersistFieldSql (Decomposed sess) => PersistEntity (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

Associated Types

type PersistEntityBackend (PersistentSession sess) #

data Key (PersistentSession sess) #

data EntityField (PersistentSession sess) :: Type -> Type #

data Unique (PersistentSession sess) #

PersistField (Key (PersistentSession sess)) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

data Unique (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

data EntityField (PersistentSession sess) typ Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

newtype Key (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

type PersistEntityBackend (PersistentSession sess) Source # 
Instance details

Defined in Web.ServerSession.Backend.Persistent.Internal.Impl

serverSessionDefsBySessionMap :: [UnboundEntityDef] Source #

Simple version. Entity definitions needed to generate the SQL schema for SqlStorage. Example:

mkMigrate "migrateAll" serverSessionDefsBySessionMap

Note: Also import PersistentSessionBySessionMap in the same module.

mkServerSessionDefs :: forall sess. PersistEntity sess => Proxy sess -> Text -> [UnboundEntityDef] Source #

Entity definitions needed to generate the SQL schema for SqlStorage. Generate schema by specifying Haskell name in Text.

Example using SessionMap:

type PersistentSessionBySessionMap = PersistentSession SessionMap
mkMigrate "migrateAll" (mkServerSessionDefs (Proxy :: Proxy PersistentSessionBySessionMap) "PersistentSessionBySessionMap")