polysemy-account-0.2.0.0: Account management with Servant and Polysemy
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Account.Effect.Accounts

Description

 
Synopsis

Documentation

data Accounts i p :: Effect where Source #

This effect provides common operations for account and password management.

The first parameter is the ID type for both accounts and authentication data, which might be UUID or Int.

The second parameter encodes an accounts basic privileges, mainly used for API authorization.

Constructors

Authenticate :: AccountName -> RawPassword -> Accounts i p m (Uid i (AccountAuth i))

Check credentials against the storage backend.

GeneratePassword :: i -> Maybe Datetime -> Accounts i p m GeneratedPassword

Generate a fresh password.

Create :: AccountName -> Accounts i p m (Uid i (Account p))

Add an account to the storage backend, without authentication.

FinalizeCreate :: i -> Accounts i p m (Uid i (Account p))

Mark an account as fully created.

AddPassword :: i -> RawPassword -> Maybe Datetime -> Accounts i p m (Uid i (AccountAuth i))

Associate an account with a new password, with optional expiry time.

SetStatus :: i -> AccountStatus -> Accounts i p m ()

Update the status of an account.

ById :: i -> Accounts i p m (Uid i (Account p))

Look up an account by its ID.

ByName :: AccountName -> Accounts i p m (Uid i (Account p))

Look up an account by its name.

Authed :: i -> Accounts i p m (AuthedAccount i p)

Look up an account and return its auth info.

Update :: Uid i (Account p) -> Accounts i p m ()

Overwrite an existing account.

Privileges :: i -> Accounts i p m p

Look up an account's privileges.

UpdatePrivileges :: i -> (p -> p) -> Accounts i p m ()

Update an account's privileges.

All :: Accounts i p m [Uid i (Account p)]

Fetch all accounts.

AllAuths :: Accounts i p m [Uid i (AccountAuth i)]

Fetch all auth records.

allAuths :: forall i p r. Member (Accounts i p) r => Sem r [Uid i (AccountAuth i)] Source #

Fetch all auth records.

all :: forall i p r. Member (Accounts i p) r => Sem r [Uid i (Account p)] Source #

Fetch all accounts.

updatePrivileges :: forall i p r. Member (Accounts i p) r => i -> (p -> p) -> Sem r () Source #

Update an account's privileges.

privileges :: forall i p r. Member (Accounts i p) r => i -> Sem r p Source #

Look up an account's privileges.

update :: forall i p r. Member (Accounts i p) r => Uid i (Account p) -> Sem r () Source #

Overwrite an existing account.

authed :: forall i p r. Member (Accounts i p) r => i -> Sem r (AuthedAccount i p) Source #

Look up an account and return its auth info.

byName :: forall i p r. Member (Accounts i p) r => AccountName -> Sem r (Uid i (Account p)) Source #

Look up an account by its name.

byId :: forall i p r. Member (Accounts i p) r => i -> Sem r (Uid i (Account p)) Source #

Look up an account by its ID.

setStatus :: forall i p r. Member (Accounts i p) r => i -> AccountStatus -> Sem r () Source #

Update the status of an account.

addPassword :: forall i p r. Member (Accounts i p) r => i -> RawPassword -> Maybe Datetime -> Sem r (Uid i (AccountAuth i)) Source #

Associate an account with a new password, with optional expiry time.

finalizeCreate :: forall i p r. Member (Accounts i p) r => i -> Sem r (Uid i (Account p)) Source #

Mark an account as fully created.

create :: forall i p r. Member (Accounts i p) r => AccountName -> Sem r (Uid i (Account p)) Source #

Add an account to the storage backend, without authentication.

generatePassword :: forall i p r. Member (Accounts i p) r => i -> Maybe Datetime -> Sem r GeneratedPassword Source #

Generate a fresh password.

authenticate :: forall i p r. Member (Accounts i p) r => AccountName -> RawPassword -> Sem r (Uid i (AccountAuth i)) Source #

Check credentials against the storage backend.

type AccountsP i = Accounts i [Privilege] Source #

Convenience alias for Accounts using the default Privilege type.