servant-auth-token-api-0.1.0.0: Servant based API for token based authorisation

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

Servant.API.Auth.Token

Contents

Description

 

Synopsis

API specs

type AuthSigninMethod = "auth" :> ("signin" :> (QueryParam "login" Login :> (QueryParam "password" Password :> (QueryParam "expire" Seconds :> Get '[JSON] (OnlyField "token" SimpleToken))))) Source #

How to get a token, expire of Nothing means some default value (server config)

type AuthTouchMethod = "auth" :> ("touch" :> (QueryParam "expire" Seconds :> (TokenHeader '[] :> Post '[JSON] ()))) Source #

Client cat expand the token lifetime, no permissions are required

type AuthTokenInfoMethod = "auth" :> ("token" :> (TokenHeader '[] :> Get '[JSON] RespUserInfo)) Source #

Get client info that is binded to the token

type AuthSignoutMethod = "auth" :> ("signout" :> (TokenHeader '[] :> Post '[JSON] ())) Source #

Close session, after call of the method the token in header is not valid.

type AuthSignupMethod = "auth" :> ("signup" :> (ReqBody '[JSON] ReqRegister :> (TokenHeader '["auth-register"] :> Post '[JSON] (OnlyField "user" UserId)))) Source #

Creation of new user, requires registerPerm for token

type AuthUsersMethod = "auth" :> ("users" :> (PageParam :> (PageSizeParam :> (TokenHeader '["auth-info"] :> Get '[JSON] RespUsersInfo)))) Source #

Getting list of all users, requires authInfoPerm for token

type AuthGetUserMethod = "auth" :> ("user" :> (Capture "user-id" UserId :> (TokenHeader '["auth-info"] :> Get '[JSON] RespUserInfo))) Source #

Getting info about user, requires authInfoPerm for token

type AuthPatchUserMethod = "auth" :> ("user" :> (Capture "user-id" UserId :> (ReqBody '[JSON] PatchUser :> (TokenHeader '["auth-update"] :> Patch '[JSON] ())))) Source #

Updating loginemailpassword, requires authUpdatePerm for token

type AuthPutUserMethod = "auth" :> ("user" :> (Capture "user-id" UserId :> (ReqBody '[JSON] ReqRegister :> (TokenHeader '["auth-update"] :> Put '[JSON] ())))) Source #

Replace user with the user in the body, requires authUpdatePerm for token

type AuthDeleteUserMethod = "auth" :> ("user" :> (Capture "user-id" UserId :> (TokenHeader '["auth-delete"] :> Delete '[JSON] ()))) Source #

Delete user from DB, requires authDeletePerm and will cause cascade deletion, that is your usually want

type AuthRestoreMethod = "auth" :> ("restore" :> (Capture "user-id" UserId :> (QueryParam "code" RestoreCode :> (QueryParam "password" Password :> Post '[JSON] ())))) Source #

Generate new password for user. There is two phases, first, the method is called without code parameter. The system sends email with a restore code to user email or sms (its depends on server). After that a call of the method with the code is needed to change password.

type AuthGetGroupMethod = "auth" :> ("group" :> (Capture "group-id" UserGroupId :> (TokenHeader '["auth-info"] :> Get '[JSON] UserGroup))) Source #

Getting info about user group, requires authInfoPerm for token

type AuthPostGroupMethod = "auth" :> ("group" :> (ReqBody '[JSON] UserGroup :> (TokenHeader '["auth-update"] :> Post '[JSON] (OnlyId UserGroupId)))) Source #

Inserting new user group, requires authUpdatePerm for token

type AuthPutGroupMethod = "auth" :> ("group" :> (Capture "group-id" UserGroupId :> (ReqBody '[JSON] UserGroup :> (TokenHeader '["auth-update"] :> Put '[JSON] ())))) Source #

Replace info about given user group, requires authUpdatePerm for token

type AuthPatchGroupMethod = "auth" :> ("group" :> (Capture "group-id" UserGroupId :> (ReqBody '[JSON] PatchUserGroup :> (TokenHeader '["auth-update"] :> Patch '[JSON] ())))) Source #

Patch info about given user group, requires authUpdatePerm for token

type AuthDeleteGroupMethod = "auth" :> ("group" :> (Capture "group-id" UserGroupId :> (TokenHeader '["auth-delete"] :> Delete '[JSON] ()))) Source #

Delete all info about given user group, requires authDeletePerm for token

type AuthGroupsMethod = "auth" :> ("group" :> (PageParam :> (PageSizeParam :> (TokenHeader '["auth-info"] :> Get '[JSON] (PagedList UserGroupId UserGroup))))) Source #

Get list of user groups, requires authInfoPerm for token

authAPI :: Proxy AuthAPI Source #

Proxy type for auth API, used to pass the type-level info into client/docs generation functions

authDocs :: API Source #

Servant.Docs documentation of the Auth API

Token

newtype Token perms Source #

Token is simple string marked by permissions that are expected from the token to pass guarding functions.

Constructors

Token 

Fields

Instances

Eq (Token perms) Source # 

Methods

(==) :: Token perms -> Token perms -> Bool #

(/=) :: Token perms -> Token perms -> Bool #

Show (Token perms) Source # 

Methods

showsPrec :: Int -> Token perms -> ShowS #

show :: Token perms -> String #

showList :: [Token perms] -> ShowS #

ToHttpApiData (Token perms) Source # 

Methods

toUrlPiece :: Token perms -> Text #

toHeader :: Token perms -> ByteString #

toQueryParam :: Token perms -> Text #

FromHttpApiData (Token perms) Source # 
ToSample (Token perms) Source # 

Methods

toSamples :: Proxy * (Token perms) -> [(Text, Token perms)] #

ToParamSchema (Token perms) Source # 

Methods

toParamSchema :: proxy (Token perms) -> ParamSchema t #

type MToken perms = Maybe (Token perms) Source #

Shortcut for Maybe Token with attached permissions

type TokenHeader perms = Header "Authorization" (Token perms) Source #

Token header that we require for authorization marked by permissions that are expected from the token to pass guarding functions.

type SimpleToken = Text Source #

Token that doesn't have attached compile-time permissions

class PermsList a where Source #

Minimal complete definition

unliftPerms

Methods

unliftPerms :: forall proxy. proxy a -> [Permission] Source #

Instances

PermsList ([] Symbol) Source # 

Methods

unliftPerms :: proxy [Symbol] -> [Permission] Source #

(KnownSymbol x, PermsList xs) => PermsList ((:) Symbol x xs) Source # 

Methods

unliftPerms :: proxy ((Symbol ': x) xs) -> [Permission] Source #

downgradeToken' :: True ~ PermsSubset ts' ts => Token ts -> Token ts' Source #

Cast token to permissions that are lower than original one

The cast is safe, the permissions are cheked on compile time.

downgradeToken :: True ~ PermsSubset ts' ts => MToken ts -> MToken ts' Source #

Cast token to permissions that are lower than original one.

The cast is safe, the permissions are cheked on compile time.

User

type UserId = Word Source #

Id of user that is used in the API

type Login = Text Source #

User name for login

type Password = Text Source #

Password for login

type Email = Text Source #

User email

type Permission = Text Source #

Special tag for a permission that a user has

type Seconds = Word Source #

Amount of seconds

type RestoreCode = Text Source #

Special tag for password restore

data ReqRegister Source #

Request body for user registration

Instances

Show ReqRegister Source # 
Generic ReqRegister Source # 

Associated Types

type Rep ReqRegister :: * -> * #

ToJSON ReqRegister Source # 
FromJSON ReqRegister Source # 
ToSchema ReqRegister Source # 
ToSample ReqRegister Source # 
type Rep ReqRegister Source # 
type Rep ReqRegister = D1 (MetaData "ReqRegister" "Servant.API.Auth.Token" "servant-auth-token-api-0.1.0.0-ytdrdPO8IZ81Ej6YqyzUX" False) (C1 (MetaCons "ReqRegister" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "reqRegLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Login)) (S1 (MetaSel (Just Symbol "reqRegPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Password))) ((:*:) (S1 (MetaSel (Just Symbol "reqRegEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Email)) ((:*:) (S1 (MetaSel (Just Symbol "reqRegPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Permission])) (S1 (MetaSel (Just Symbol "reqRegGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserGroupId])))))))

data RespUserInfo Source #

Response with user info

Instances

Show RespUserInfo Source # 
Generic RespUserInfo Source # 

Associated Types

type Rep RespUserInfo :: * -> * #

ToJSON RespUserInfo Source # 
FromJSON RespUserInfo Source # 
ToSchema RespUserInfo Source # 
ToSample RespUserInfo Source # 
type Rep RespUserInfo Source # 
type Rep RespUserInfo = D1 (MetaData "RespUserInfo" "Servant.API.Auth.Token" "servant-auth-token-api-0.1.0.0-ytdrdPO8IZ81Ej6YqyzUX" False) (C1 (MetaCons "RespUserInfo" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "respUserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UserId)) (S1 (MetaSel (Just Symbol "respUserLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Login))) ((:*:) (S1 (MetaSel (Just Symbol "respUserEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Email)) ((:*:) (S1 (MetaSel (Just Symbol "respUserPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Permission])) (S1 (MetaSel (Just Symbol "respUserGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [UserGroupId]))))))

data PatchUser Source #

Request body for patching user

Instances

Show PatchUser Source # 
Generic PatchUser Source # 

Associated Types

type Rep PatchUser :: * -> * #

ToJSON PatchUser Source # 
FromJSON PatchUser Source # 
ToSchema PatchUser Source # 
ToSample PatchUser Source # 
type Rep PatchUser Source # 
type Rep PatchUser = D1 (MetaData "PatchUser" "Servant.API.Auth.Token" "servant-auth-token-api-0.1.0.0-ytdrdPO8IZ81Ej6YqyzUX" False) (C1 (MetaCons "PatchUser" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "patchUserLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Login))) (S1 (MetaSel (Just Symbol "patchUserPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Password)))) ((:*:) (S1 (MetaSel (Just Symbol "patchUserEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Email))) ((:*:) (S1 (MetaSel (Just Symbol "patchUserPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Permission]))) (S1 (MetaSel (Just Symbol "patchUserGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserGroupId])))))))

User groups

type UserGroupId = Word Source #

Id of user group

data UserGroup Source #

Data of user group, groups allows to group permissions and assign them to particular users in batch manner.

Also a group hierarchy can be formed.

data PatchUserGroup Source #

Data type that is used to patch UserGroup

Instances

Show PatchUserGroup Source # 
Generic PatchUserGroup Source # 

Associated Types

type Rep PatchUserGroup :: * -> * #

ToJSON PatchUserGroup Source # 
FromJSON PatchUserGroup Source # 
ToSchema PatchUserGroup Source # 
ToSample PatchUserGroup Source # 
type Rep PatchUserGroup Source # 
type Rep PatchUserGroup = D1 (MetaData "PatchUserGroup" "Servant.API.Auth.Token" "servant-auth-token-api-0.1.0.0-ytdrdPO8IZ81Ej6YqyzUX" False) (C1 (MetaCons "PatchUserGroup" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "patchUserGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "patchUserGroupUsers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserId])))) ((:*:) (S1 (MetaSel (Just Symbol "patchUserGroupPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Permission]))) ((:*:) (S1 (MetaSel (Just Symbol "patchUserGroupParent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UserGroupId))) (S1 (MetaSel (Just Symbol "patchUserGroupNoParent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))

Default permissions

adminPerm :: Permission Source #

Permission that allows everything by default

registerPerm :: Permission Source #

Permission that allows registration of new users

authInfoPerm :: Permission Source #

Permission that allows to query info about other users

authUpdatePerm :: Permission Source #

Permission that allows to update fields of an user

authDeletePerm :: Permission Source #

Permission that allows to delete users and cause cascade deletion

Swagger helpers

authOperations :: Traversal' Swagger Operation Source #

Select only operations of the Auth API

Reexports

Orphan instances

ToSample Word Source # 

Methods

toSamples :: Proxy * Word -> [(Text, Word)] #

ToSample () Source # 

Methods

toSamples :: Proxy * () -> [(Text, ())] #

ToSample Text Source # 

Methods

toSamples :: Proxy * Text -> [(Text, Text)] #

ToParam * (QueryParam * "code" RestoreCode) Source # 
ToParam * (QueryParam * "expire" Seconds) Source # 

Methods

toParam :: Proxy (QueryParam * "expire" Seconds) t -> DocQueryParam #

ToParam * (QueryParam * "login" Login) Source # 

Methods

toParam :: Proxy (QueryParam * "login" Login) t -> DocQueryParam #

ToParam * (QueryParam * "password" Password) Source # 

Methods

toParam :: Proxy (QueryParam * "password" Password) t -> DocQueryParam #

ToCapture * (Capture * "group-id" UserGroupId) Source # 

Methods

toCapture :: Proxy (Capture * "group-id" UserGroupId) c -> DocCapture #

ToCapture * (Capture * "user-id" UserId) Source # 

Methods

toCapture :: Proxy (Capture * "user-id" UserId) c -> DocCapture #