servant-auth-token-0.4.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 #

Internal user implementation

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 #

type Rep UserImpl Source # 
type Rep UserImpl = D1 (MetaData "UserImpl" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" 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 UserPerm Source #

Internal implementation of permission (1-M)

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 #

type Rep UserPerm Source # 
type Rep UserPerm = D1 (MetaData "UserPerm" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" False) (C1 (MetaCons "UserPerm" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "userPermUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UserImplId)) (S1 (MetaSel (Just Symbol "userPermPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Permission))))

data AuthToken Source #

Internal implementation of authorisation token

Constructors

AuthToken 

Fields

Instances

Show AuthToken Source # 
Generic AuthToken Source # 

Associated Types

type Rep AuthToken :: * -> * #

type Rep AuthToken Source # 
type Rep AuthToken = D1 (MetaData "AuthToken" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" 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 UserImplId)) (S1 (MetaSel (Just Symbol "authTokenExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)))))

data UserRestore Source #

Internal implementation of restoration code

Constructors

UserRestore 

Fields

Instances

Show UserRestore Source # 
Generic UserRestore Source # 

Associated Types

type Rep UserRestore :: * -> * #

type Rep UserRestore Source # 
type Rep UserRestore = D1 (MetaData "UserRestore" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" 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 UserImplId)) (S1 (MetaSel (Just Symbol "userRestoreExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)))))

data AuthUserGroup Source #

Internal implementation of user group

Constructors

AuthUserGroup 

Fields

Instances

Show AuthUserGroup Source # 
Generic AuthUserGroup Source # 

Associated Types

type Rep AuthUserGroup :: * -> * #

type Rep AuthUserGroup Source # 
type Rep AuthUserGroup = D1 (MetaData "AuthUserGroup" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" 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 AuthUserGroupId)))))

data AuthUserGroupUsers Source #

Implementation of M-M between user and group

Instances

Show AuthUserGroupUsers Source # 
Generic AuthUserGroupUsers Source # 
type Rep AuthUserGroupUsers Source # 
type Rep AuthUserGroupUsers = D1 (MetaData "AuthUserGroupUsers" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" False) (C1 (MetaCons "AuthUserGroupUsers" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "authUserGroupUsersGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AuthUserGroupId)) (S1 (MetaSel (Just Symbol "authUserGroupUsersUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UserImplId))))

data AuthUserGroupPerms Source #

Implementation of M-M between permission and group

Instances

Show AuthUserGroupPerms Source # 
Generic AuthUserGroupPerms Source # 
type Rep AuthUserGroupPerms Source # 
type Rep AuthUserGroupPerms = D1 (MetaData "AuthUserGroupPerms" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" False) (C1 (MetaCons "AuthUserGroupPerms" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "authUserGroupPermsGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AuthUserGroupId)) (S1 (MetaSel (Just Symbol "authUserGroupPermsPermission") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Permission))))

data UserSingleUseCode Source #

Internal implementation of single use code

Constructors

UserSingleUseCode 

Fields

Instances

Show UserSingleUseCode Source # 
Generic UserSingleUseCode Source # 
type Rep UserSingleUseCode Source # 
type Rep UserSingleUseCode = D1 (MetaData "UserSingleUseCode" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" 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 UserImplId))) ((:*:) (S1 (MetaSel (Just Symbol "userSingleUseCodeExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UTCTime))) (S1 (MetaSel (Just Symbol "userSingleUseCodeUsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UTCTime))))))

IDs of entities

data UserImplId Source #

ID of user

data UserPermId Source #

ID of user permission

data AuthUserGroupUsersId Source #

ID of user-group binding

Instances

Eq AuthUserGroupUsersId Source # 
Ord AuthUserGroupUsersId Source # 
Show AuthUserGroupUsersId Source # 
Generic AuthUserGroupUsersId Source # 
ConvertableKey AuthUserGroupUsersId Source # 
type Rep AuthUserGroupUsersId Source # 
type Rep AuthUserGroupUsersId = D1 (MetaData "AuthUserGroupUsersId" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" True) (C1 (MetaCons "AuthUserGroupUsersId" PrefixI True) (S1 (MetaSel (Just Symbol "unAuthUserGroupUsersId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

data AuthUserGroupPermsId Source #

ID of permission-group binding

Instances

Eq AuthUserGroupPermsId Source # 
Ord AuthUserGroupPermsId Source # 
Show AuthUserGroupPermsId Source # 
Generic AuthUserGroupPermsId Source # 
ConvertableKey AuthUserGroupPermsId Source # 
type Rep AuthUserGroupPermsId Source # 
type Rep AuthUserGroupPermsId = D1 (MetaData "AuthUserGroupPermsId" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" True) (C1 (MetaCons "AuthUserGroupPermsId" PrefixI True) (S1 (MetaSel (Just Symbol "unAuthUserGroupPermsId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

data UserSingleUseCodeId Source #

ID of single use code

Instances

Eq UserSingleUseCodeId Source # 
Ord UserSingleUseCodeId Source # 
Show UserSingleUseCodeId Source # 
Generic UserSingleUseCodeId Source # 
ConvertableKey UserSingleUseCodeId Source # 
type Rep UserSingleUseCodeId Source # 
type Rep UserSingleUseCodeId = D1 (MetaData "UserSingleUseCodeId" "Servant.Server.Auth.Token.Model" "servant-auth-token-0.4.2.0-6icbkKaBFEYIDBrGIqJCRw" True) (C1 (MetaCons "UserSingleUseCodeId" PrefixI True) (S1 (MetaSel (Just Symbol "unUserSingleUseCodeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

DB interface

class MonadIO m => HasStorage m where Source #

Abstract storage interface. External libraries can implement this in terms of PostgreSQL or acid-state.

Methods

getUserImpl :: UserImplId -> m (Maybe UserImpl) Source #

Getting user from storage

getUserImplByLogin :: Login -> m (Maybe (WithId UserImplId UserImpl)) Source #

Getting user from storage by login

listUsersPaged :: Page -> PageSize -> m ([WithId UserImplId UserImpl], Word) Source #

Get paged list of users and total count of users

getUserImplPermissions :: UserImplId -> m [WithId UserPermId UserPerm] Source #

Get user permissions, ascending by tag

deleteUserPermissions :: UserImplId -> m () Source #

Delete user permissions

insertUserPerm :: UserPerm -> m UserPermId Source #

Insertion of new user permission

insertUserImpl :: UserImpl -> m UserImplId Source #

Insertion of new user

replaceUserImpl :: UserImplId -> UserImpl -> m () Source #

Replace user with new value

deleteUserImpl :: UserImplId -> m () Source #

Delete user by id

hasPerm :: UserImplId -> Permission -> m Bool Source #

Check whether the user has particular permission

getFirstUserByPerm :: Permission -> m (Maybe (WithId UserImplId UserImpl)) Source #

Get any user with given permission

selectUserImplGroups :: UserImplId -> m [WithId AuthUserGroupUsersId AuthUserGroupUsers] Source #

Select user groups and sort them by ascending name

clearUserImplGroups :: UserImplId -> m () Source #

Remove user from all groups

insertAuthUserGroup :: AuthUserGroup -> m AuthUserGroupId Source #

Add new user group

insertAuthUserGroupUsers :: AuthUserGroupUsers -> m AuthUserGroupUsersId Source #

Add user to given group

insertAuthUserGroupPerms :: AuthUserGroupPerms -> m AuthUserGroupPermsId Source #

Add permission to given group

getAuthUserGroup :: AuthUserGroupId -> m (Maybe AuthUserGroup) Source #

Find user group by id

listAuthUserGroupPermissions :: AuthUserGroupId -> m [WithId AuthUserGroupPermsId AuthUserGroupPerms] Source #

Get list of permissions of given group

listAuthUserGroupUsers :: AuthUserGroupId -> m [WithId AuthUserGroupUsersId AuthUserGroupUsers] Source #

Get list of all users of the group

replaceAuthUserGroup :: AuthUserGroupId -> AuthUserGroup -> m () Source #

Replace record of user group

clearAuthUserGroupUsers :: AuthUserGroupId -> m () Source #

Remove all users from group

clearAuthUserGroupPerms :: AuthUserGroupId -> m () Source #

Remove all permissions from group

deleteAuthUserGroup :: AuthUserGroupId -> m () Source #

Delete user group from storage

listGroupsPaged :: Page -> PageSize -> m ([WithId AuthUserGroupId AuthUserGroup], Word) Source #

Get paged list of user groups with total count

setAuthUserGroupName :: AuthUserGroupId -> Text -> m () Source #

Set group name

setAuthUserGroupParent :: AuthUserGroupId -> Maybe AuthUserGroupId -> m () Source #

Set group parent

insertSingleUseCode :: UserSingleUseCode -> m UserSingleUseCodeId Source #

Add new single use code

setSingleUseCodeUsed :: UserSingleUseCodeId -> Maybe UTCTime -> m () Source #

Set usage time of the single use code

getUnusedCode :: SingleUseCode -> UserImplId -> UTCTime -> m (Maybe (WithId UserSingleUseCodeId UserSingleUseCode)) Source #

Find unused code for the user and expiration time greater than the given time

invalidatePermamentCodes :: UserImplId -> UTCTime -> m () Source #

Invalidate all permament codes for user and set use time for them

selectLastRestoreCode :: UserImplId -> UTCTime -> m (Maybe (WithId UserRestoreId UserRestore)) Source #

Select last valid restoration code by the given current time

insertUserRestore :: UserRestore -> m UserRestoreId Source #

Insert new restore code

findRestoreCode :: UserImplId -> RestoreCode -> UTCTime -> m (Maybe (WithId UserRestoreId UserRestore)) Source #

Find unexpired by the time restore code

replaceRestoreCode :: UserRestoreId -> UserRestore -> m () Source #

Replace restore code with new value

findAuthToken :: UserImplId -> UTCTime -> m (Maybe (WithId AuthTokenId AuthToken)) Source #

Find first non-expired by the time token for user

findAuthTokenByValue :: SimpleToken -> m (Maybe (WithId AuthTokenId AuthToken)) Source #

Find token by value

insertAuthToken :: AuthToken -> m AuthTokenId Source #

Insert new token

replaceAuthToken :: AuthTokenId -> AuthToken -> m () Source #

Replace auth token with new value

Operations

passToByteString :: Password -> ByteString Source #

Convert password to bytestring

byteStringToPass :: ByteString -> Password Source #

Convert bytestring into password

User

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

Helper to convert user to response

readUserInfo :: HasStorage m => UserId -> m (Maybe RespUserInfo) Source #

Get user by id

getUserPermissions :: HasStorage m => UserImplId -> m [Permission] Source #

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

setUserPermissions :: HasStorage m => UserImplId -> [Permission] -> m () Source #

Return list of permissions for the given user

createUser :: HasStorage m => Int -> Login -> Password -> Email -> [Permission] -> m UserImplId Source #

Creation of new user

hasPerms :: HasStorage m => UserImplId -> [Permission] -> m Bool Source #

Check whether the user has particular permissions

createAdmin :: HasStorage m => Int -> Login -> Password -> Email -> m UserImplId Source #

Creates user with admin privileges

ensureAdmin :: HasStorage m => Int -> Login -> Password -> Email -> m () Source #

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

patchUser Source #

Arguments

:: HasStorage m 
=> Int

Password strength

-> PatchUser 
-> WithId UserImplId UserImpl 
-> m (WithId UserImplId UserImpl) 

Apply patches for user

setUserPassword' Source #

Arguments

:: MonadIO m 
=> Int

Password strength

-> Password 
-> UserImpl 
-> m UserImpl 

Update password of user

User groups

getUserGroups :: HasStorage m => UserImplId -> m [UserGroupId] Source #

Get all groups the user belongs to

setUserGroups :: HasStorage m => UserImplId -> [UserGroupId] -> m () Source #

Rewrite all user groups

validateGroups :: HasStorage m => [UserGroupId] -> m [AuthUserGroupId] Source #

Leave only existing groups

getGroupPermissions :: HasStorage m => UserGroupId -> m [Permission] Source #

Getting permission of a group and all it parent groups

getUserGroupPermissions :: HasStorage m => UserImplId -> m [Permission] Source #

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

getUserAllPermissions :: HasStorage m => UserImplId -> m [Permission] Source #

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

readUserGroup :: HasStorage m => UserGroupId -> m (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 :: HasStorage m => UserGroup -> m UserGroupId Source #

Insert user group into RDBMS

updateUserGroup :: HasStorage m => UserGroupId -> UserGroup -> m () Source #

Replace user group with new value

deleteUserGroup :: HasStorage m => UserGroupId -> m () Source #

Erase user group from RDBMS, cascade

patchUserGroup :: HasStorage m => UserGroupId -> PatchUserGroup -> m () Source #

Partial update of user group