servant-auth-token-0.3.2.0: Servant based API and server for token based authorisation

Copyright(c) Anton Gushcha, 2016
LicenseMIT
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Servant.Server.Auth.Token.Model

Contents

Description

 

Synopsis

DB entities

data UserImpl Source #

Constructors

UserImpl 

Fields

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 # 

Methods

sqlType :: Proxy * UserImpl -> SqlType

PersistField UserImpl Source # 

Methods

toPersistValue :: UserImpl -> PersistValue

fromPersistValue :: PersistValue -> Either Text UserImpl

PersistEntity UserImpl Source # 

Associated Types

type PersistEntityBackend UserImpl :: *

data Key UserImpl :: *

data EntityField UserImpl a :: * #

data Unique UserImpl :: *

Methods

keyToValues :: Key UserImpl -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key UserImpl)

persistIdField :: EntityField UserImpl (Key UserImpl)

entityDef :: Monad m => m UserImpl -> EntityDef

persistFieldDef :: EntityField UserImpl typ -> FieldDef

toPersistFields :: UserImpl -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text UserImpl

persistUniqueKeys :: UserImpl -> [Unique UserImpl]

persistUniqueToFieldNames :: Unique UserImpl -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique UserImpl -> [PersistValue]

fieldLens :: EntityField UserImpl field -> forall f. Functor f => (field -> f field) -> Entity UserImpl -> f (Entity UserImpl)

ToBackendKey SqlBackend UserImpl Source # 

Methods

toBackendKey :: Key UserImpl -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key UserImpl

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

Methods

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

Eq (Key UserImpl) Source # 

Methods

(==) :: Key UserImpl -> Key UserImpl -> Bool #

(/=) :: Key UserImpl -> Key UserImpl -> Bool #

Ord (Key UserImpl) Source # 

Methods

compare :: Key UserImpl -> Key UserImpl -> Ordering #

(<) :: Key UserImpl -> Key UserImpl -> Bool #

(<=) :: Key UserImpl -> Key UserImpl -> Bool #

(>) :: Key UserImpl -> Key UserImpl -> Bool #

(>=) :: Key UserImpl -> Key UserImpl -> Bool #

max :: Key UserImpl -> Key UserImpl -> Key UserImpl #

min :: Key UserImpl -> Key UserImpl -> Key UserImpl #

Read (Key UserImpl) Source # 
Show (Key UserImpl) Source # 

Methods

showsPrec :: Int -> Key UserImpl -> ShowS #

show :: Key UserImpl -> String #

showList :: [Key UserImpl] -> ShowS #

PersistFieldSql (Key UserImpl) Source # 

Methods

sqlType :: Proxy * (Key UserImpl) -> SqlType

PersistField (Key UserImpl) Source # 

Methods

toPersistValue :: Key UserImpl -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key UserImpl)

ToJSON (Key UserImpl) Source # 

Methods

toJSON :: Key UserImpl -> Value

toEncoding :: Key UserImpl -> Encoding

ToHttpApiData (Key UserImpl) Source # 

Methods

toUrlPiece :: Key UserImpl -> Text

toHeader :: Key UserImpl -> ByteString

toQueryParam :: Key UserImpl -> Text

FromJSON (Key UserImpl) Source # 

Methods

parseJSON :: Value -> Parser (Key UserImpl)

FromHttpApiData (Key UserImpl) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key UserImpl)

parseHeader :: ByteString -> Either Text (Key UserImpl)

parseQueryParam :: Text -> Either Text (Key UserImpl)

PathPiece (Key UserImpl) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key UserImpl)

toPathPiece :: Key UserImpl -> Text

type Rep UserImpl Source # 
type Rep UserImpl = D1 (MetaData "UserImpl" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique UserImpl = UniqueLogin Login
type PersistEntityBackend UserImpl Source # 
type PersistEntityBackend UserImpl = SqlBackend
data Key UserImpl Source # 
data Key UserImpl = UserImplKey {}
data EntityField UserImpl Source # 

data UserPerm Source #

Constructors

UserPerm 

Fields

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 # 

Methods

sqlType :: Proxy * UserPerm -> SqlType

PersistField UserPerm Source # 

Methods

toPersistValue :: UserPerm -> PersistValue

fromPersistValue :: PersistValue -> Either Text UserPerm

PersistEntity UserPerm Source # 

Associated Types

type PersistEntityBackend UserPerm :: *

data Key UserPerm :: *

data EntityField UserPerm a :: * #

data Unique UserPerm :: *

Methods

keyToValues :: Key UserPerm -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key UserPerm)

persistIdField :: EntityField UserPerm (Key UserPerm)

entityDef :: Monad m => m UserPerm -> EntityDef

persistFieldDef :: EntityField UserPerm typ -> FieldDef

toPersistFields :: UserPerm -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text UserPerm

persistUniqueKeys :: UserPerm -> [Unique UserPerm]

persistUniqueToFieldNames :: Unique UserPerm -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique UserPerm -> [PersistValue]

fieldLens :: EntityField UserPerm field -> forall f. Functor f => (field -> f field) -> Entity UserPerm -> f (Entity UserPerm)

ToBackendKey SqlBackend UserPerm Source # 

Methods

toBackendKey :: Key UserPerm -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key UserPerm

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

Methods

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

Eq (Key UserPerm) Source # 

Methods

(==) :: Key UserPerm -> Key UserPerm -> Bool #

(/=) :: Key UserPerm -> Key UserPerm -> Bool #

Ord (Key UserPerm) Source # 

Methods

compare :: Key UserPerm -> Key UserPerm -> Ordering #

(<) :: Key UserPerm -> Key UserPerm -> Bool #

(<=) :: Key UserPerm -> Key UserPerm -> Bool #

(>) :: Key UserPerm -> Key UserPerm -> Bool #

(>=) :: Key UserPerm -> Key UserPerm -> Bool #

max :: Key UserPerm -> Key UserPerm -> Key UserPerm #

min :: Key UserPerm -> Key UserPerm -> Key UserPerm #

Read (Key UserPerm) Source # 
Show (Key UserPerm) Source # 

Methods

showsPrec :: Int -> Key UserPerm -> ShowS #

show :: Key UserPerm -> String #

showList :: [Key UserPerm] -> ShowS #

PersistFieldSql (Key UserPerm) Source # 

Methods

sqlType :: Proxy * (Key UserPerm) -> SqlType

PersistField (Key UserPerm) Source # 

Methods

toPersistValue :: Key UserPerm -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key UserPerm)

ToJSON (Key UserPerm) Source # 

Methods

toJSON :: Key UserPerm -> Value

toEncoding :: Key UserPerm -> Encoding

ToHttpApiData (Key UserPerm) Source # 

Methods

toUrlPiece :: Key UserPerm -> Text

toHeader :: Key UserPerm -> ByteString

toQueryParam :: Key UserPerm -> Text

FromJSON (Key UserPerm) Source # 

Methods

parseJSON :: Value -> Parser (Key UserPerm)

FromHttpApiData (Key UserPerm) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key UserPerm)

parseHeader :: ByteString -> Either Text (Key UserPerm)

parseQueryParam :: Text -> Either Text (Key UserPerm)

PathPiece (Key UserPerm) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key UserPerm)

toPathPiece :: Key UserPerm -> Text

type Rep UserPerm Source # 
type Rep UserPerm = D1 (MetaData "UserPerm" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique UserPerm
type PersistEntityBackend UserPerm Source # 
type PersistEntityBackend UserPerm = SqlBackend
data Key UserPerm Source # 
data Key UserPerm = UserPermKey {}
data EntityField UserPerm Source # 

data AuthToken Source #

Constructors

AuthToken 

Fields

Instances

Show AuthToken Source # 
Generic AuthToken Source # 

Associated Types

type Rep AuthToken :: * -> * #

PersistFieldSql AuthToken Source # 

Methods

sqlType :: Proxy * AuthToken -> SqlType

PersistField AuthToken Source # 

Methods

toPersistValue :: AuthToken -> PersistValue

fromPersistValue :: PersistValue -> Either Text AuthToken

PersistEntity AuthToken Source # 

Associated Types

type PersistEntityBackend AuthToken :: *

data Key AuthToken :: *

data EntityField AuthToken a :: * #

data Unique AuthToken :: *

Methods

keyToValues :: Key AuthToken -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key AuthToken)

persistIdField :: EntityField AuthToken (Key AuthToken)

entityDef :: Monad m => m AuthToken -> EntityDef

persistFieldDef :: EntityField AuthToken typ -> FieldDef

toPersistFields :: AuthToken -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text AuthToken

persistUniqueKeys :: AuthToken -> [Unique AuthToken]

persistUniqueToFieldNames :: Unique AuthToken -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique AuthToken -> [PersistValue]

fieldLens :: EntityField AuthToken field -> forall f. Functor f => (field -> f field) -> Entity AuthToken -> f (Entity AuthToken)

ToBackendKey SqlBackend AuthToken Source # 

Methods

toBackendKey :: Key AuthToken -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key AuthToken

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

Methods

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

Eq (Key AuthToken) Source # 

Methods

(==) :: Key AuthToken -> Key AuthToken -> Bool #

(/=) :: Key AuthToken -> Key AuthToken -> Bool #

Ord (Key AuthToken) Source # 

Methods

compare :: Key AuthToken -> Key AuthToken -> Ordering #

(<) :: Key AuthToken -> Key AuthToken -> Bool #

(<=) :: Key AuthToken -> Key AuthToken -> Bool #

(>) :: Key AuthToken -> Key AuthToken -> Bool #

(>=) :: Key AuthToken -> Key AuthToken -> Bool #

max :: Key AuthToken -> Key AuthToken -> Key AuthToken #

min :: Key AuthToken -> Key AuthToken -> Key AuthToken #

Read (Key AuthToken) Source # 
Show (Key AuthToken) Source # 

Methods

showsPrec :: Int -> Key AuthToken -> ShowS #

show :: Key AuthToken -> String #

showList :: [Key AuthToken] -> ShowS #

PersistFieldSql (Key AuthToken) Source # 

Methods

sqlType :: Proxy * (Key AuthToken) -> SqlType

PersistField (Key AuthToken) Source # 

Methods

toPersistValue :: Key AuthToken -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key AuthToken)

ToJSON (Key AuthToken) Source # 

Methods

toJSON :: Key AuthToken -> Value

toEncoding :: Key AuthToken -> Encoding

ToHttpApiData (Key AuthToken) Source # 

Methods

toUrlPiece :: Key AuthToken -> Text

toHeader :: Key AuthToken -> ByteString

toQueryParam :: Key AuthToken -> Text

FromJSON (Key AuthToken) Source # 

Methods

parseJSON :: Value -> Parser (Key AuthToken)

FromHttpApiData (Key AuthToken) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key AuthToken)

parseHeader :: ByteString -> Either Text (Key AuthToken)

parseQueryParam :: Text -> Either Text (Key AuthToken)

PathPiece (Key AuthToken) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key AuthToken)

toPathPiece :: Key AuthToken -> Text

type Rep AuthToken Source # 
type Rep AuthToken = D1 (MetaData "AuthToken" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique AuthToken
type PersistEntityBackend AuthToken Source # 
type PersistEntityBackend AuthToken = SqlBackend
data Key AuthToken Source # 
data Key AuthToken = AuthTokenKey {}
data EntityField AuthToken Source # 

data UserRestore Source #

Constructors

UserRestore 

Fields

Instances

Show UserRestore Source # 
Generic UserRestore Source # 

Associated Types

type Rep UserRestore :: * -> * #

PersistFieldSql UserRestore Source # 

Methods

sqlType :: Proxy * UserRestore -> SqlType

PersistField UserRestore Source # 

Methods

toPersistValue :: UserRestore -> PersistValue

fromPersistValue :: PersistValue -> Either Text UserRestore

PersistEntity UserRestore Source # 

Associated Types

type PersistEntityBackend UserRestore :: *

data Key UserRestore :: *

data EntityField UserRestore a :: * #

data Unique UserRestore :: *

Methods

keyToValues :: Key UserRestore -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key UserRestore)

persistIdField :: EntityField UserRestore (Key UserRestore)

entityDef :: Monad m => m UserRestore -> EntityDef

persistFieldDef :: EntityField UserRestore typ -> FieldDef

toPersistFields :: UserRestore -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text UserRestore

persistUniqueKeys :: UserRestore -> [Unique UserRestore]

persistUniqueToFieldNames :: Unique UserRestore -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique UserRestore -> [PersistValue]

fieldLens :: EntityField UserRestore field -> forall f. Functor f => (field -> f field) -> Entity UserRestore -> f (Entity UserRestore)

ToBackendKey SqlBackend UserRestore Source # 

Methods

toBackendKey :: Key UserRestore -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key UserRestore

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

Methods

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

Eq (Key UserRestore) Source # 

Methods

(==) :: Key UserRestore -> Key UserRestore -> Bool #

(/=) :: Key UserRestore -> Key UserRestore -> Bool #

Ord (Key UserRestore) Source # 

Methods

compare :: Key UserRestore -> Key UserRestore -> Ordering #

(<) :: Key UserRestore -> Key UserRestore -> Bool #

(<=) :: Key UserRestore -> Key UserRestore -> Bool #

(>) :: Key UserRestore -> Key UserRestore -> Bool #

(>=) :: Key UserRestore -> Key UserRestore -> Bool #

max :: Key UserRestore -> Key UserRestore -> Key UserRestore #

min :: Key UserRestore -> Key UserRestore -> Key UserRestore #

Read (Key UserRestore) Source # 
Show (Key UserRestore) Source # 

Methods

showsPrec :: Int -> Key UserRestore -> ShowS #

show :: Key UserRestore -> String #

showList :: [Key UserRestore] -> ShowS #

PersistFieldSql (Key UserRestore) Source # 

Methods

sqlType :: Proxy * (Key UserRestore) -> SqlType

PersistField (Key UserRestore) Source # 

Methods

toPersistValue :: Key UserRestore -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key UserRestore)

ToJSON (Key UserRestore) Source # 

Methods

toJSON :: Key UserRestore -> Value

toEncoding :: Key UserRestore -> Encoding

ToHttpApiData (Key UserRestore) Source # 

Methods

toUrlPiece :: Key UserRestore -> Text

toHeader :: Key UserRestore -> ByteString

toQueryParam :: Key UserRestore -> Text

FromJSON (Key UserRestore) Source # 

Methods

parseJSON :: Value -> Parser (Key UserRestore)

FromHttpApiData (Key UserRestore) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key UserRestore)

parseHeader :: ByteString -> Either Text (Key UserRestore)

parseQueryParam :: Text -> Either Text (Key UserRestore)

PathPiece (Key UserRestore) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key UserRestore)

toPathPiece :: Key UserRestore -> Text

type Rep UserRestore Source # 
type Rep UserRestore = D1 (MetaData "UserRestore" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique UserRestore
type PersistEntityBackend UserRestore Source # 
type PersistEntityBackend UserRestore = SqlBackend
data Key UserRestore Source # 
data Key UserRestore = UserRestoreKey {}
data EntityField UserRestore Source # 

data AuthUserGroup Source #

Constructors

AuthUserGroup 

Instances

Show AuthUserGroup Source # 
Generic AuthUserGroup Source # 

Associated Types

type Rep AuthUserGroup :: * -> * #

PersistFieldSql AuthUserGroup Source # 

Methods

sqlType :: Proxy * AuthUserGroup -> SqlType

PersistField AuthUserGroup Source # 

Methods

toPersistValue :: AuthUserGroup -> PersistValue

fromPersistValue :: PersistValue -> Either Text AuthUserGroup

PersistEntity AuthUserGroup Source # 

Associated Types

type PersistEntityBackend AuthUserGroup :: *

data Key AuthUserGroup :: *

data EntityField AuthUserGroup a :: * #

data Unique AuthUserGroup :: *

Methods

keyToValues :: Key AuthUserGroup -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key AuthUserGroup)

persistIdField :: EntityField AuthUserGroup (Key AuthUserGroup)

entityDef :: Monad m => m AuthUserGroup -> EntityDef

persistFieldDef :: EntityField AuthUserGroup typ -> FieldDef

toPersistFields :: AuthUserGroup -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text AuthUserGroup

persistUniqueKeys :: AuthUserGroup -> [Unique AuthUserGroup]

persistUniqueToFieldNames :: Unique AuthUserGroup -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique AuthUserGroup -> [PersistValue]

fieldLens :: EntityField AuthUserGroup field -> forall f. Functor f => (field -> f field) -> Entity AuthUserGroup -> f (Entity AuthUserGroup)

ToBackendKey SqlBackend AuthUserGroup Source # 

Methods

toBackendKey :: Key AuthUserGroup -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key AuthUserGroup

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

Methods

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

Eq (Key AuthUserGroup) Source # 

Methods

(==) :: Key AuthUserGroup -> Key AuthUserGroup -> Bool #

(/=) :: Key AuthUserGroup -> Key AuthUserGroup -> Bool #

Ord (Key AuthUserGroup) Source # 
Read (Key AuthUserGroup) Source # 
Show (Key AuthUserGroup) Source # 
PersistFieldSql (Key AuthUserGroup) Source # 

Methods

sqlType :: Proxy * (Key AuthUserGroup) -> SqlType

PersistField (Key AuthUserGroup) Source # 

Methods

toPersistValue :: Key AuthUserGroup -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key AuthUserGroup)

ToJSON (Key AuthUserGroup) Source # 

Methods

toJSON :: Key AuthUserGroup -> Value

toEncoding :: Key AuthUserGroup -> Encoding

ToHttpApiData (Key AuthUserGroup) Source # 
FromJSON (Key AuthUserGroup) Source # 

Methods

parseJSON :: Value -> Parser (Key AuthUserGroup)

FromHttpApiData (Key AuthUserGroup) Source # 

Methods

parseUrlPiece :: Text -> Either Text (Key AuthUserGroup)

parseHeader :: ByteString -> Either Text (Key AuthUserGroup)

parseQueryParam :: Text -> Either Text (Key AuthUserGroup)

PathPiece (Key AuthUserGroup) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key AuthUserGroup)

toPathPiece :: Key AuthUserGroup -> Text

type Rep AuthUserGroup Source # 
type Rep AuthUserGroup = D1 (MetaData "AuthUserGroup" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique AuthUserGroup
type PersistEntityBackend AuthUserGroup Source # 
type PersistEntityBackend AuthUserGroup = SqlBackend
data Key AuthUserGroup Source # 
data Key AuthUserGroup = AuthUserGroupKey {}
data EntityField AuthUserGroup Source # 

data AuthUserGroupUsers Source #

Instances

Show AuthUserGroupUsers Source # 
Generic AuthUserGroupUsers Source # 
PersistFieldSql AuthUserGroupUsers Source # 

Methods

sqlType :: Proxy * AuthUserGroupUsers -> SqlType

PersistField AuthUserGroupUsers Source # 

Methods

toPersistValue :: AuthUserGroupUsers -> PersistValue

fromPersistValue :: PersistValue -> Either Text AuthUserGroupUsers

PersistEntity AuthUserGroupUsers Source # 

Associated Types

type PersistEntityBackend AuthUserGroupUsers :: *

data Key AuthUserGroupUsers :: *

data EntityField AuthUserGroupUsers a :: * #

data Unique AuthUserGroupUsers :: *

Methods

keyToValues :: Key AuthUserGroupUsers -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key AuthUserGroupUsers)

persistIdField :: EntityField AuthUserGroupUsers (Key AuthUserGroupUsers)

entityDef :: Monad m => m AuthUserGroupUsers -> EntityDef

persistFieldDef :: EntityField AuthUserGroupUsers typ -> FieldDef

toPersistFields :: AuthUserGroupUsers -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text AuthUserGroupUsers

persistUniqueKeys :: AuthUserGroupUsers -> [Unique AuthUserGroupUsers]

persistUniqueToFieldNames :: Unique AuthUserGroupUsers -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique AuthUserGroupUsers -> [PersistValue]

fieldLens :: EntityField AuthUserGroupUsers field -> forall f. Functor f => (field -> f field) -> Entity AuthUserGroupUsers -> f (Entity AuthUserGroupUsers)

ToBackendKey SqlBackend AuthUserGroupUsers Source # 

Methods

toBackendKey :: Key AuthUserGroupUsers -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key AuthUserGroupUsers

(PersistQuery backend, (~) * (PersistEntityBackend AuthUserGroupUsers) (BaseBackend backend)) => DeleteCascade AuthUserGroupUsers backend Source # 

Methods

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

Eq (Key AuthUserGroupUsers) Source # 
Ord (Key AuthUserGroupUsers) Source # 
Read (Key AuthUserGroupUsers) Source # 
Show (Key AuthUserGroupUsers) Source # 
PersistFieldSql (Key AuthUserGroupUsers) Source # 

Methods

sqlType :: Proxy * (Key AuthUserGroupUsers) -> SqlType

PersistField (Key AuthUserGroupUsers) Source # 

Methods

toPersistValue :: Key AuthUserGroupUsers -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key AuthUserGroupUsers)

ToJSON (Key AuthUserGroupUsers) Source # 

Methods

toJSON :: Key AuthUserGroupUsers -> Value

toEncoding :: Key AuthUserGroupUsers -> Encoding

ToHttpApiData (Key AuthUserGroupUsers) Source # 
FromJSON (Key AuthUserGroupUsers) Source # 

Methods

parseJSON :: Value -> Parser (Key AuthUserGroupUsers)

FromHttpApiData (Key AuthUserGroupUsers) Source # 
PathPiece (Key AuthUserGroupUsers) Source # 
type Rep AuthUserGroupUsers Source # 
type Rep AuthUserGroupUsers = D1 (MetaData "AuthUserGroupUsers" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique AuthUserGroupUsers
type PersistEntityBackend AuthUserGroupUsers Source # 
type PersistEntityBackend AuthUserGroupUsers = SqlBackend
data Key AuthUserGroupUsers Source # 
data EntityField AuthUserGroupUsers Source # 

data AuthUserGroupPerms Source #

Instances

Show AuthUserGroupPerms Source # 
Generic AuthUserGroupPerms Source # 
PersistFieldSql AuthUserGroupPerms Source # 

Methods

sqlType :: Proxy * AuthUserGroupPerms -> SqlType

PersistField AuthUserGroupPerms Source # 

Methods

toPersistValue :: AuthUserGroupPerms -> PersistValue

fromPersistValue :: PersistValue -> Either Text AuthUserGroupPerms

PersistEntity AuthUserGroupPerms Source # 

Associated Types

type PersistEntityBackend AuthUserGroupPerms :: *

data Key AuthUserGroupPerms :: *

data EntityField AuthUserGroupPerms a :: * #

data Unique AuthUserGroupPerms :: *

Methods

keyToValues :: Key AuthUserGroupPerms -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key AuthUserGroupPerms)

persistIdField :: EntityField AuthUserGroupPerms (Key AuthUserGroupPerms)

entityDef :: Monad m => m AuthUserGroupPerms -> EntityDef

persistFieldDef :: EntityField AuthUserGroupPerms typ -> FieldDef

toPersistFields :: AuthUserGroupPerms -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text AuthUserGroupPerms

persistUniqueKeys :: AuthUserGroupPerms -> [Unique AuthUserGroupPerms]

persistUniqueToFieldNames :: Unique AuthUserGroupPerms -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique AuthUserGroupPerms -> [PersistValue]

fieldLens :: EntityField AuthUserGroupPerms field -> forall f. Functor f => (field -> f field) -> Entity AuthUserGroupPerms -> f (Entity AuthUserGroupPerms)

ToBackendKey SqlBackend AuthUserGroupPerms Source # 

Methods

toBackendKey :: Key AuthUserGroupPerms -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key AuthUserGroupPerms

(PersistQuery backend, (~) * (PersistEntityBackend AuthUserGroupPerms) (BaseBackend backend)) => DeleteCascade AuthUserGroupPerms backend Source # 

Methods

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

Eq (Key AuthUserGroupPerms) Source # 
Ord (Key AuthUserGroupPerms) Source # 
Read (Key AuthUserGroupPerms) Source # 
Show (Key AuthUserGroupPerms) Source # 
PersistFieldSql (Key AuthUserGroupPerms) Source # 

Methods

sqlType :: Proxy * (Key AuthUserGroupPerms) -> SqlType

PersistField (Key AuthUserGroupPerms) Source # 

Methods

toPersistValue :: Key AuthUserGroupPerms -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key AuthUserGroupPerms)

ToJSON (Key AuthUserGroupPerms) Source # 

Methods

toJSON :: Key AuthUserGroupPerms -> Value

toEncoding :: Key AuthUserGroupPerms -> Encoding

ToHttpApiData (Key AuthUserGroupPerms) Source # 
FromJSON (Key AuthUserGroupPerms) Source # 

Methods

parseJSON :: Value -> Parser (Key AuthUserGroupPerms)

FromHttpApiData (Key AuthUserGroupPerms) Source # 
PathPiece (Key AuthUserGroupPerms) Source # 
type Rep AuthUserGroupPerms Source # 
type Rep AuthUserGroupPerms = D1 (MetaData "AuthUserGroupPerms" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique AuthUserGroupPerms
type PersistEntityBackend AuthUserGroupPerms Source # 
type PersistEntityBackend AuthUserGroupPerms = SqlBackend
data Key AuthUserGroupPerms Source # 
data EntityField AuthUserGroupPerms Source # 

data family EntityField record a :: * #

Instances

data EntityField AuthUserGroupPerms # 
data EntityField AuthUserGroupUsers # 
data EntityField AuthUserGroup # 
data EntityField UserSingleUseCode # 
data EntityField UserRestore # 
data EntityField AuthToken # 
data EntityField UserPerm # 
data EntityField UserImpl # 

data UserSingleUseCode Source #

Instances

Show UserSingleUseCode Source # 
Generic UserSingleUseCode Source # 
PersistFieldSql UserSingleUseCode Source # 

Methods

sqlType :: Proxy * UserSingleUseCode -> SqlType

PersistField UserSingleUseCode Source # 

Methods

toPersistValue :: UserSingleUseCode -> PersistValue

fromPersistValue :: PersistValue -> Either Text UserSingleUseCode

PersistEntity UserSingleUseCode Source # 

Associated Types

type PersistEntityBackend UserSingleUseCode :: *

data Key UserSingleUseCode :: *

data EntityField UserSingleUseCode a :: * #

data Unique UserSingleUseCode :: *

Methods

keyToValues :: Key UserSingleUseCode -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key UserSingleUseCode)

persistIdField :: EntityField UserSingleUseCode (Key UserSingleUseCode)

entityDef :: Monad m => m UserSingleUseCode -> EntityDef

persistFieldDef :: EntityField UserSingleUseCode typ -> FieldDef

toPersistFields :: UserSingleUseCode -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text UserSingleUseCode

persistUniqueKeys :: UserSingleUseCode -> [Unique UserSingleUseCode]

persistUniqueToFieldNames :: Unique UserSingleUseCode -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique UserSingleUseCode -> [PersistValue]

fieldLens :: EntityField UserSingleUseCode field -> forall f. Functor f => (field -> f field) -> Entity UserSingleUseCode -> f (Entity UserSingleUseCode)

ToBackendKey SqlBackend UserSingleUseCode Source # 

Methods

toBackendKey :: Key UserSingleUseCode -> BackendKey SqlBackend

fromBackendKey :: BackendKey SqlBackend -> Key UserSingleUseCode

(PersistQuery backend, (~) * (PersistEntityBackend UserSingleUseCode) (BaseBackend backend)) => DeleteCascade UserSingleUseCode backend Source # 

Methods

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

Eq (Key UserSingleUseCode) Source # 
Ord (Key UserSingleUseCode) Source # 
Read (Key UserSingleUseCode) Source # 
Show (Key UserSingleUseCode) Source # 
PersistFieldSql (Key UserSingleUseCode) Source # 

Methods

sqlType :: Proxy * (Key UserSingleUseCode) -> SqlType

PersistField (Key UserSingleUseCode) Source # 

Methods

toPersistValue :: Key UserSingleUseCode -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key UserSingleUseCode)

ToJSON (Key UserSingleUseCode) Source # 

Methods

toJSON :: Key UserSingleUseCode -> Value

toEncoding :: Key UserSingleUseCode -> Encoding

ToHttpApiData (Key UserSingleUseCode) Source # 
FromJSON (Key UserSingleUseCode) Source # 

Methods

parseJSON :: Value -> Parser (Key UserSingleUseCode)

FromHttpApiData (Key UserSingleUseCode) Source # 
PathPiece (Key UserSingleUseCode) Source # 

Methods

fromPathPiece :: Text -> Maybe (Key UserSingleUseCode)

toPathPiece :: Key UserSingleUseCode -> Text

type Rep UserSingleUseCode Source # 
type Rep UserSingleUseCode = D1 (MetaData "UserSingleUseCode" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.3.2.0-6P5olFkNRPc8iz1OVYHvKR" 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 Unique UserSingleUseCode
type PersistEntityBackend UserSingleUseCode Source # 
type PersistEntityBackend UserSingleUseCode = SqlBackend
data Key UserSingleUseCode Source # 
data Key UserSingleUseCode = UserSingleUseCodeKey {}
data EntityField UserSingleUseCode Source # 

IDs of entities

Operations

runDB :: (MonadReader AuthConfig m, MonadIO m) => SqlPersistT IO b -> m b Source #

Execute database transaction

migrateAll :: Migration Source #

passToByteString :: Password -> ByteString Source #

Convert password to bytestring

byteStringToPass :: ByteString -> Password Source #

Convert bytestring into password

User

userToUserInfo :: Entity UserImpl -> [Permission] -> [UserGroupId] -> RespUserInfo Source #

Helper to convert user to response

readUserInfo :: UserId -> SqlPersistT IO (Maybe RespUserInfo) Source #

Get user by id

readUserInfoByLogin :: Login -> SqlPersistT IO (Maybe RespUserInfo) Source #

Get user by login

getUserPermissions :: UserImplId -> SqlPersistT IO [Permission] Source #

Return list of permissions for the given user (only permissions that are assigned to him directly)

setUserPermissions :: UserImplId -> [Permission] -> SqlPersistT IO () Source #

Return list of permissions for the given user

createUser :: Int -> Login -> Password -> Email -> [Permission] -> SqlPersistT IO UserImplId Source #

Creation of new user

hasPerm :: UserImplId -> Permission -> SqlPersistT IO Bool Source #

Check whether the user has particular permission

hasPerms :: UserImplId -> [Permission] -> SqlPersistT IO Bool Source #

Check whether the user has particular permissions

createAdmin :: Int -> Login -> Password -> Email -> SqlPersistT IO UserImplId Source #

Creates user with admin privileges

ensureAdmin :: Int -> Login -> Password -> Email -> SqlPersistT IO () Source #

Ensures that DB has at leas one admin, if not, creates a new one with specified info.

patchUser Source #

Arguments

:: Int

Password strength

-> PatchUser 
-> Entity UserImpl 
-> SqlPersistT IO (Entity UserImpl) 

Apply patches for user

setUserPassword' Source #

Arguments

:: MonadIO m 
=> Int

Password strength

-> Password 
-> UserImpl 
-> m UserImpl 

Update password of user

User groups

getUserGroups :: UserImplId -> SqlPersistT IO [UserGroupId] Source #

Get all groups the user belongs to

setUserGroups :: UserImplId -> [UserGroupId] -> SqlPersistT IO () Source #

Rewrite all user groups

validateGroups :: [UserGroupId] -> SqlPersistT IO [AuthUserGroupId] Source #

Leave only existing groups

getGroupPermissions :: UserGroupId -> SqlPersistT IO [Permission] Source #

Getting permission of a group and all it parent groups

getUserGroupPermissions :: UserImplId -> SqlPersistT IO [Permission] Source #

Get user permissions that are assigned to him/her via groups only

getUserAllPermissions :: UserImplId -> SqlPersistT IO [Permission] Source #

Get user permissions that are assigned to him/her either by direct way or by his/her groups.

readUserGroup :: UserGroupId -> SqlPersistT IO (Maybe UserGroup) Source #

Collect full info about user group from RDBMS

toAuthUserGroup :: UserGroup -> (AuthUserGroup, AuthUserGroupId -> [AuthUserGroupUsers], AuthUserGroupId -> [AuthUserGroupPerms]) Source #

Helper to convert user group into values of several tables

insertUserGroup :: UserGroup -> SqlPersistT IO UserGroupId Source #

Insert user group into RDBMS

updateUserGroup :: UserGroupId -> UserGroup -> SqlPersistT IO () Source #

Replace user group with new value

deleteUserGroup :: UserGroupId -> SqlPersistT IO () Source #

Erase user group from RDBMS, cascade

patchUserGroup :: UserGroupId -> PatchUserGroup -> SqlPersistT IO () Source #

Partial update of user group