servant-auth-token-persistent-0.6.1.0: Persistent backend for servant-auth-token server

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Auth.Token.Persistent.Schema

Synopsis

Documentation

data UserImpl Source #

Instances

Show UserImpl Source # 
Generic UserImpl Source # 

Associated Types

type Rep UserImpl :: * -> * #

Methods

from :: UserImpl -> Rep UserImpl x #

to :: Rep UserImpl x -> UserImpl #

PersistFieldSql UserImpl Source # 
PersistEntity UserImpl Source # 
PersistField UserImpl Source # 
(PersistQuery backend, (~) * (PersistEntityBackend UserImpl) (BaseBackend backend)) => DeleteCascade UserImpl backend Source # 

Methods

deleteCascade :: MonadIO m => Key UserImpl -> ReaderT * backend m () #

ToBackendKey SqlBackend UserImpl Source # 
ConvertStorage UserImplId UserImplId Source # 
ConvertStorage UserImpl UserImpl Source # 
Eq (Key UserImpl) Source # 
Ord (Key UserImpl) Source # 
Read (Key UserImpl) Source # 
Show (Key UserImpl) Source # 
ToJSON (Key UserImpl) Source # 
FromJSON (Key UserImpl) Source # 
ToHttpApiData (Key UserImpl) Source # 
FromHttpApiData (Key UserImpl) Source # 
PathPiece (Key UserImpl) Source # 
PersistFieldSql (Key UserImpl) Source # 
PersistField (Key UserImpl) Source # 
type Rep UserImpl Source # 
type Rep UserImpl = D1 * (MetaData "UserImpl" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "UserImpl" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "userImplLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Login)) ((:*:) * (S1 * (MetaSel (Just Symbol "userImplPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Password)) (S1 * (MetaSel (Just Symbol "userImplEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Email)))))
data Unique UserImpl Source # 
data EntityField UserImpl Source # 
data Key UserImpl Source # 
type PersistEntityBackend UserImpl Source # 

data UserPerm Source #

Instances

Show UserPerm Source # 
Generic UserPerm Source # 

Associated Types

type Rep UserPerm :: * -> * #

Methods

from :: UserPerm -> Rep UserPerm x #

to :: Rep UserPerm x -> UserPerm #

PersistFieldSql UserPerm Source # 
PersistEntity UserPerm Source # 
PersistField UserPerm Source # 
(PersistQuery backend, (~) * (PersistEntityBackend UserPerm) (BaseBackend backend)) => DeleteCascade UserPerm backend Source # 

Methods

deleteCascade :: MonadIO m => Key UserPerm -> ReaderT * backend m () #

ToBackendKey SqlBackend UserPerm Source # 
ConvertStorage UserPermId UserPermId Source # 
ConvertStorage UserPerm UserPerm Source # 
Eq (Key UserPerm) Source # 
Ord (Key UserPerm) Source # 
Read (Key UserPerm) Source # 
Show (Key UserPerm) Source # 
ToJSON (Key UserPerm) Source # 
FromJSON (Key UserPerm) Source # 
ToHttpApiData (Key UserPerm) Source # 
FromHttpApiData (Key UserPerm) Source # 
PathPiece (Key UserPerm) Source # 
PersistFieldSql (Key UserPerm) Source # 
PersistField (Key UserPerm) Source # 
type Rep UserPerm Source # 
type Rep UserPerm = D1 * (MetaData "UserPerm" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "UserPerm" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "userPermUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key UserImpl))) (S1 * (MetaSel (Just Symbol "userPermPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Permission))))
data Unique UserPerm Source # 
data EntityField UserPerm Source # 
data Key UserPerm Source # 
type PersistEntityBackend UserPerm Source # 

data AuthToken Source #

Instances

Show AuthToken Source # 
Generic AuthToken Source # 

Associated Types

type Rep AuthToken :: * -> * #

PersistFieldSql AuthToken Source # 
PersistEntity AuthToken Source # 
PersistField AuthToken Source # 
(PersistQuery backend, (~) * (PersistEntityBackend AuthToken) (BaseBackend backend)) => DeleteCascade AuthToken backend Source # 

Methods

deleteCascade :: MonadIO m => Key AuthToken -> ReaderT * backend m () #

ToBackendKey SqlBackend AuthToken Source # 
ConvertStorage AuthTokenId AuthTokenId Source # 
ConvertStorage AuthToken AuthToken Source # 
Eq (Key AuthToken) Source # 
Ord (Key AuthToken) Source # 
Read (Key AuthToken) Source # 
Show (Key AuthToken) Source # 
ToJSON (Key AuthToken) Source # 
FromJSON (Key AuthToken) Source # 
ToHttpApiData (Key AuthToken) Source # 
FromHttpApiData (Key AuthToken) Source # 
PathPiece (Key AuthToken) Source # 
PersistFieldSql (Key AuthToken) Source # 
PersistField (Key AuthToken) Source # 
type Rep AuthToken Source # 
type Rep AuthToken = D1 * (MetaData "AuthToken" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "AuthToken" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "authTokenValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SimpleToken)) ((:*:) * (S1 * (MetaSel (Just Symbol "authTokenUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key UserImpl))) (S1 * (MetaSel (Just Symbol "authTokenExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))
data Unique AuthToken Source # 
data EntityField AuthToken Source # 
data Key AuthToken Source # 
type PersistEntityBackend AuthToken Source # 

data UserRestore Source #

Instances

Show UserRestore Source # 
Generic UserRestore Source # 

Associated Types

type Rep UserRestore :: * -> * #

PersistFieldSql UserRestore Source # 
PersistEntity UserRestore Source # 
PersistField UserRestore Source # 
(PersistQuery backend, (~) * (PersistEntityBackend UserRestore) (BaseBackend backend)) => DeleteCascade UserRestore backend Source # 

Methods

deleteCascade :: MonadIO m => Key UserRestore -> ReaderT * backend m () #

ToBackendKey SqlBackend UserRestore Source # 
ConvertStorage UserRestoreId UserRestoreId Source # 
ConvertStorage UserRestore UserRestore Source # 
Eq (Key UserRestore) Source # 
Ord (Key UserRestore) Source # 
Read (Key UserRestore) Source # 
Show (Key UserRestore) Source # 
ToJSON (Key UserRestore) Source # 
FromJSON (Key UserRestore) Source # 
ToHttpApiData (Key UserRestore) Source # 
FromHttpApiData (Key UserRestore) Source # 
PathPiece (Key UserRestore) Source # 
PersistFieldSql (Key UserRestore) Source # 
PersistField (Key UserRestore) Source # 
type Rep UserRestore Source # 
type Rep UserRestore = D1 * (MetaData "UserRestore" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "UserRestore" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "userRestoreValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * RestoreCode)) ((:*:) * (S1 * (MetaSel (Just Symbol "userRestoreUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key UserImpl))) (S1 * (MetaSel (Just Symbol "userRestoreExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))
data Unique UserRestore Source # 
data EntityField UserRestore Source # 
data Key UserRestore Source # 
type PersistEntityBackend UserRestore Source # 

data UserSingleUseCode Source #

Instances

Show UserSingleUseCode Source # 
Generic UserSingleUseCode Source # 
PersistFieldSql UserSingleUseCode Source # 
PersistEntity UserSingleUseCode Source # 
PersistField UserSingleUseCode Source # 
(PersistQuery backend, (~) * (PersistEntityBackend UserSingleUseCode) (BaseBackend backend)) => DeleteCascade UserSingleUseCode backend Source # 

Methods

deleteCascade :: MonadIO m => Key UserSingleUseCode -> ReaderT * backend m () #

ToBackendKey SqlBackend UserSingleUseCode Source # 
ConvertStorage UserSingleUseCodeId UserSingleUseCodeId Source # 
ConvertStorage UserSingleUseCode UserSingleUseCode Source # 
Eq (Key UserSingleUseCode) Source # 
Ord (Key UserSingleUseCode) Source # 
Read (Key UserSingleUseCode) Source # 
Show (Key UserSingleUseCode) Source # 
ToJSON (Key UserSingleUseCode) Source # 
FromJSON (Key UserSingleUseCode) Source # 
ToHttpApiData (Key UserSingleUseCode) Source # 
FromHttpApiData (Key UserSingleUseCode) Source # 
PathPiece (Key UserSingleUseCode) Source # 
PersistFieldSql (Key UserSingleUseCode) Source # 
PersistField (Key UserSingleUseCode) Source # 
type Rep UserSingleUseCode Source # 
type Rep UserSingleUseCode = D1 * (MetaData "UserSingleUseCode" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "UserSingleUseCode" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "userSingleUseCodeValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SingleUseCode)) (S1 * (MetaSel (Just Symbol "userSingleUseCodeUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key UserImpl)))) ((:*:) * (S1 * (MetaSel (Just Symbol "userSingleUseCodeExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UTCTime))) (S1 * (MetaSel (Just Symbol "userSingleUseCodeUsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UTCTime))))))
data Unique UserSingleUseCode Source # 
data EntityField UserSingleUseCode Source # 
data Key UserSingleUseCode Source # 
type PersistEntityBackend UserSingleUseCode Source # 

data AuthUserGroup Source #

Instances

Show AuthUserGroup Source # 
Generic AuthUserGroup Source # 

Associated Types

type Rep AuthUserGroup :: * -> * #

PersistFieldSql AuthUserGroup Source # 
PersistEntity AuthUserGroup Source # 
PersistField AuthUserGroup Source # 
(PersistQuery backend, (~) * (PersistEntityBackend AuthUserGroup) (BaseBackend backend)) => DeleteCascade AuthUserGroup backend Source # 

Methods

deleteCascade :: MonadIO m => Key AuthUserGroup -> ReaderT * backend m () #

ToBackendKey SqlBackend AuthUserGroup Source # 
ConvertStorage AuthUserGroupId AuthUserGroupId Source # 
ConvertStorage AuthUserGroup AuthUserGroup Source # 
Eq (Key AuthUserGroup) Source # 
Ord (Key AuthUserGroup) Source # 
Read (Key AuthUserGroup) Source # 
Show (Key AuthUserGroup) Source # 
ToJSON (Key AuthUserGroup) Source # 
FromJSON (Key AuthUserGroup) Source # 
ToHttpApiData (Key AuthUserGroup) Source # 
FromHttpApiData (Key AuthUserGroup) Source # 
PathPiece (Key AuthUserGroup) Source # 
PersistFieldSql (Key AuthUserGroup) Source # 
PersistField (Key AuthUserGroup) Source # 
type Rep AuthUserGroup Source # 
type Rep AuthUserGroup = D1 * (MetaData "AuthUserGroup" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "AuthUserGroup" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "authUserGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "authUserGroupParent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Key AuthUserGroup))))))
data Unique AuthUserGroup Source # 
data EntityField AuthUserGroup Source # 
data Key AuthUserGroup Source # 
type PersistEntityBackend AuthUserGroup Source # 

data AuthUserGroupUsers Source #

Instances

Show AuthUserGroupUsers Source # 
Generic AuthUserGroupUsers Source # 
PersistFieldSql AuthUserGroupUsers Source # 
PersistEntity AuthUserGroupUsers Source # 
PersistField AuthUserGroupUsers Source # 
(PersistQuery backend, (~) * (PersistEntityBackend AuthUserGroupUsers) (BaseBackend backend)) => DeleteCascade AuthUserGroupUsers backend Source # 

Methods

deleteCascade :: MonadIO m => Key AuthUserGroupUsers -> ReaderT * backend m () #

ToBackendKey SqlBackend AuthUserGroupUsers Source # 
ConvertStorage AuthUserGroupUsersId AuthUserGroupUsersId Source # 
ConvertStorage AuthUserGroupUsers AuthUserGroupUsers Source # 
Eq (Key AuthUserGroupUsers) Source # 
Ord (Key AuthUserGroupUsers) Source # 
Read (Key AuthUserGroupUsers) Source # 
Show (Key AuthUserGroupUsers) Source # 
ToJSON (Key AuthUserGroupUsers) Source # 
FromJSON (Key AuthUserGroupUsers) Source # 
ToHttpApiData (Key AuthUserGroupUsers) Source # 
FromHttpApiData (Key AuthUserGroupUsers) Source # 
PathPiece (Key AuthUserGroupUsers) Source # 
PersistFieldSql (Key AuthUserGroupUsers) Source # 
PersistField (Key AuthUserGroupUsers) Source # 
type Rep AuthUserGroupUsers Source # 
type Rep AuthUserGroupUsers = D1 * (MetaData "AuthUserGroupUsers" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "AuthUserGroupUsers" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "authUserGroupUsersGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key AuthUserGroup))) (S1 * (MetaSel (Just Symbol "authUserGroupUsersUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key UserImpl)))))
data Unique AuthUserGroupUsers Source # 
data EntityField AuthUserGroupUsers Source # 
data Key AuthUserGroupUsers Source # 
type PersistEntityBackend AuthUserGroupUsers Source # 

data AuthUserGroupPerms Source #

Instances

Show AuthUserGroupPerms Source # 
Generic AuthUserGroupPerms Source # 
PersistFieldSql AuthUserGroupPerms Source # 
PersistEntity AuthUserGroupPerms Source # 
PersistField AuthUserGroupPerms Source # 
(PersistQuery backend, (~) * (PersistEntityBackend AuthUserGroupPerms) (BaseBackend backend)) => DeleteCascade AuthUserGroupPerms backend Source # 

Methods

deleteCascade :: MonadIO m => Key AuthUserGroupPerms -> ReaderT * backend m () #

ToBackendKey SqlBackend AuthUserGroupPerms Source # 
ConvertStorage AuthUserGroupPermsId AuthUserGroupPermsId Source # 
ConvertStorage AuthUserGroupPerms AuthUserGroupPerms Source # 
Eq (Key AuthUserGroupPerms) Source # 
Ord (Key AuthUserGroupPerms) Source # 
Read (Key AuthUserGroupPerms) Source # 
Show (Key AuthUserGroupPerms) Source # 
ToJSON (Key AuthUserGroupPerms) Source # 
FromJSON (Key AuthUserGroupPerms) Source # 
ToHttpApiData (Key AuthUserGroupPerms) Source # 
FromHttpApiData (Key AuthUserGroupPerms) Source # 
PathPiece (Key AuthUserGroupPerms) Source # 
PersistFieldSql (Key AuthUserGroupPerms) Source # 
PersistField (Key AuthUserGroupPerms) Source # 
type Rep AuthUserGroupPerms Source # 
type Rep AuthUserGroupPerms = D1 * (MetaData "AuthUserGroupPerms" "Servant.Server.Auth.Token.Persistent.Schema" "servant-auth-token-persistent-0.6.1.0-APIqPmvnotpE5Q4ZnOPicJ" False) (C1 * (MetaCons "AuthUserGroupPerms" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "authUserGroupPermsGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Key AuthUserGroup))) (S1 * (MetaSel (Just Symbol "authUserGroupPermsPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Permission))))
data Unique AuthUserGroupPerms Source # 
data EntityField AuthUserGroupPerms Source # 
data Key AuthUserGroupPerms Source # 
type PersistEntityBackend AuthUserGroupPerms Source # 

class ConvertStorage a b | a -> b, b -> a where Source #

Defines way to convert from persistent struct to model struct and vice versa.

Warning: default implementation is done via 'unsafeCoerce#', so make sure that structure of a and b is completely identical.

Methods

convertTo :: b -> a Source #

Convert to internal representation

convertTo :: (ToBackendKey SqlBackend r, a ~ Key r, ConvertableKey b) => b -> a Source #

Convert to internal representation

convertFrom :: a -> b Source #

Convert from internal representation

convertFrom :: (ToBackendKey SqlBackend r, a ~ Key r, ConvertableKey b) => a -> b Source #

Convert from internal representation

Instances

ConvertStorage AuthUserGroupPermsId AuthUserGroupPermsId Source # 
ConvertStorage AuthUserGroupPerms AuthUserGroupPerms Source # 
ConvertStorage AuthUserGroupUsersId AuthUserGroupUsersId Source # 
ConvertStorage AuthUserGroupUsers AuthUserGroupUsers Source # 
ConvertStorage AuthUserGroupId AuthUserGroupId Source # 
ConvertStorage AuthUserGroup AuthUserGroup Source # 
ConvertStorage UserSingleUseCodeId UserSingleUseCodeId Source # 
ConvertStorage UserSingleUseCode UserSingleUseCode Source # 
ConvertStorage UserRestoreId UserRestoreId Source # 
ConvertStorage UserRestore UserRestore Source # 
ConvertStorage AuthTokenId AuthTokenId Source # 
ConvertStorage AuthToken AuthToken Source # 
ConvertStorage UserPermId UserPermId Source # 
ConvertStorage UserPerm UserPerm Source # 
ConvertStorage UserImplId UserImplId Source # 
ConvertStorage UserImpl UserImpl Source #