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

Polysemy.Account

Description

 
Synopsis

Effects

data Accounts i p :: Effect 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.

type AccountsP i = Accounts i [Privilege] Source #

Convenience alias for Accounts using the default Privilege type.

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.

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

Generate a fresh password.

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.

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

Mark an account as fully created.

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.

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

Update the status of an account.

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.

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.

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

Overwrite an existing account.

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

Look up an account's privileges.

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

Update an account's privileges.

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

Fetch all accounts.

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

Fetch all auth records.

data Password :: Effect Source #

This effect provides password hashing, validation, and generation.

hash :: forall r. Member Password r => RawPassword -> Sem r HashedPassword Source #

Hash a clear text password.

check :: forall r. Member Password r => RawPassword -> HashedPassword -> Sem r Bool Source #

Validate a password against a hash.

generate :: forall r. Member Password r => Word -> Sem r GeneratedPassword Source #

Generate a new clear text password of the specified length.

Interpreters

interpretAccounts :: forall e i p r. Show e => Member (Query AccountByName (Maybe (Uid i (Account p))) !! e) r => Member (Query (AuthForAccount i) [Uid i (AccountAuth i)] !! e) r => Members [Password, Store i (Account p) !! e, Store i (AccountAuth i) !! e, Reader (AccountsConfig p) !! e, Id i] r => InterpreterFor (Accounts i p !! AccountsError) r Source #

Interpret Accounts using Store and Query from Polysemy.Db as the storage backend.

interpretAccountsState :: forall i p r. Ord i => Show i => Members [Log, Id i, Embed IO] r => AccountsConfig p -> [Uid i (Account p)] -> [Uid i (AccountAuth i)] -> InterpretersFor [Accounts i p !! AccountsError, Password] r Source #

Interpret Accounts and Password using AtomicState as storage backend.

interpretPassword :: Member (Embed IO) r => InterpreterFor Password r Source #

Interpret Password using the Argon2 algorithm and Data.Elocrypt-generated passwords.

interpretPasswordId :: InterpreterFor Password r Source #

Interpret Password trivially, not performing any hashing and generating sequences of asterisks.

Misc combinators

register :: Member (Accounts i p) r => AccountCredentials -> Sem r (AuthedAccount i p) Source #

Register an account with the given credentials.

Create the account in the storage backend, hash the password and store it, then mark the account as created.

login :: Member (Accounts i p) r => AccountCredentials -> Sem r (AuthedAccount i p) Source #

Authenticate the given credentials against the storage backend and return the matched account's information.

unlockAccountName :: Members [Accounts i p, Stop AccountsError] r => AccountName -> Sem r () Source #

Convenience function for unlocking the account matching the given name.

Data types

data Account p Source #

A basic user account, consisting of a name, activation status, and an arbitrary privilege type.

Constructors

Account 

Instances

Instances details
FromJSON p => FromJSON (Account p) Source # 
Instance details

Defined in Polysemy.Account.Data.Account

ToJSON p => ToJSON (Account p) Source # 
Instance details

Defined in Polysemy.Account.Data.Account

Generic (Account p) Source # 
Instance details

Defined in Polysemy.Account.Data.Account

Associated Types

type Rep (Account p) :: Type -> Type #

Methods

from :: Account p -> Rep (Account p) x #

to :: Rep (Account p) x -> Account p #

Show p => Show (Account p) Source # 
Instance details

Defined in Polysemy.Account.Data.Account

Methods

showsPrec :: Int -> Account p -> ShowS #

show :: Account p -> String #

showList :: [Account p] -> ShowS #

Eq p => Eq (Account p) Source # 
Instance details

Defined in Polysemy.Account.Data.Account

Methods

(==) :: Account p -> Account p -> Bool #

(/=) :: Account p -> Account p -> Bool #

type Rep (Account p) Source # 
Instance details

Defined in Polysemy.Account.Data.Account

type Rep (Account p) = D1 ('MetaData "Account" "Polysemy.Account.Data.Account" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: (S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountStatus) :*: S1 ('MetaSel ('Just "privileges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p))))

data AuthedAccount i p Source #

An account an the ID of the password used to authenticate it.

Constructors

AuthedAccount 

Fields

Instances

Instances details
(FromJSON i, FromJSON p) => FromJSON (AuthedAccount i p) Source # 
Instance details

Defined in Polysemy.Account.Data.AuthedAccount

(ToJSON i, ToJSON p) => ToJSON (AuthedAccount i p) Source # 
Instance details

Defined in Polysemy.Account.Data.AuthedAccount

Generic (AuthedAccount i p) Source # 
Instance details

Defined in Polysemy.Account.Data.AuthedAccount

Associated Types

type Rep (AuthedAccount i p) :: Type -> Type #

Methods

from :: AuthedAccount i p -> Rep (AuthedAccount i p) x #

to :: Rep (AuthedAccount i p) x -> AuthedAccount i p #

(Show i, Show p) => Show (AuthedAccount i p) Source # 
Instance details

Defined in Polysemy.Account.Data.AuthedAccount

(Eq i, Eq p) => Eq (AuthedAccount i p) Source # 
Instance details

Defined in Polysemy.Account.Data.AuthedAccount

Methods

(==) :: AuthedAccount i p -> AuthedAccount i p -> Bool #

(/=) :: AuthedAccount i p -> AuthedAccount i p -> Bool #

type Rep (AuthedAccount i p) Source # 
Instance details

Defined in Polysemy.Account.Data.AuthedAccount

type Rep (AuthedAccount i p) = D1 ('MetaData "AuthedAccount" "Polysemy.Account.Data.AuthedAccount" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'False) (C1 ('MetaCons "AuthedAccount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Just "authId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: (S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountStatus) :*: S1 ('MetaSel ('Just "privileges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p)))))

data AccountAuth i Source #

A hashed password associated with an account.

Constructors

AccountAuth 

Fields

Instances

Instances details
Generic (AccountAuth i) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountAuth

Associated Types

type Rep (AccountAuth i) :: Type -> Type #

Methods

from :: AccountAuth i -> Rep (AccountAuth i) x #

to :: Rep (AccountAuth i) x -> AccountAuth i #

Show i => Show (AccountAuth i) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountAuth

Eq i => Eq (AccountAuth i) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountAuth

type Rep (AccountAuth i) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountAuth

type Rep (AccountAuth i) = D1 ('MetaData "AccountAuth" "Polysemy.Account.Data.AccountAuth" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'False) (C1 ('MetaCons "AccountAuth" 'PrefixI 'True) ((S1 ('MetaSel ('Just "account") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountAuthDescription)) :*: (S1 ('MetaSel ('Just "password") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashedPassword) :*: S1 ('MetaSel ('Just "expiry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Datetime)))))

data AccountsConfig p Source #

The configuration for the interpreter for Accounts.

The defaults, when using Privilege, are:

  • Length 20
  • Don't activate accounts right away
  • Web privileges

Constructors

AccountsConfig 

Fields

Instances

Instances details
FromJSON p => FromJSON (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

ToJSON p => ToJSON (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

Generic (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

Associated Types

type Rep (AccountsConfig p) :: Type -> Type #

Show p => Show (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

Default p => Default (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

Methods

def :: AccountsConfig p #

Eq p => Eq (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

type Rep (AccountsConfig p) Source # 
Instance details

Defined in Polysemy.Account.Data.AccountsConfig

type Rep (AccountsConfig p) = D1 ('MetaData "AccountsConfig" "Polysemy.Account.Data.AccountsConfig" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'False) (C1 ('MetaCons "AccountsConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "passwordLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: (S1 ('MetaSel ('Just "initActive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "defaultPrivileges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p))))

type AccountsConfigP = AccountsConfig [Privilege] Source #

Convenience alias for using the default privilege type with AccountsConfig.

data AccountsError Source #

Errors produced by the effect Accounts.

Constructors

Client AccountsClientError

Errors that indicate invalid client-supplied information.

Internal Text

Error indicating storage backend failure.

data AccountsClientError Source #

Errors that indicate invalid client-supplied information.

Constructors

NoAccountId

No account was found for the given ID.

InvalidAuth

Credentials did not match stored auth data.

NoAccountName

No account was found for the given name.

Conflict

Name given for registration already exists in storage.

newtype AccountName Source #

The name of an account.

Constructors

AccountName 

Fields

Instances

Instances details
FromJSON AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

ToJSON AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

IsString AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

Generic AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

Associated Types

type Rep AccountName :: Type -> Type #

Show AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

Eq AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

Ord AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

type Rep AccountName Source # 
Instance details

Defined in Polysemy.Account.Data.AccountName

type Rep AccountName = D1 ('MetaData "AccountName" "Polysemy.Account.Data.AccountName" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'True) (C1 ('MetaCons "AccountName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAccountName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data RawPassword Source #

A clear text password, supplied by the user or generated.

newtype GeneratedPassword Source #

A password that was generated, intended to be shown to the user, and therefore permitted to be shown, as opposed to RawPassword.

Instances

Instances details
FromJSON GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

ToJSON GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

IsString GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

Generic GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

Associated Types

type Rep GeneratedPassword :: Type -> Type #

Show GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

Eq GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

Ord GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

type Rep GeneratedPassword Source # 
Instance details

Defined in Polysemy.Account.Data.GeneratedPassword

type Rep GeneratedPassword = D1 ('MetaData "GeneratedPassword" "Polysemy.Account.Data.GeneratedPassword" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'True) (C1 ('MetaCons "GeneratedPassword" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGeneratedPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data AccountStatus Source #

Basic account status.

Constructors

Creating

The account was added to storage, but not processed fully.

Pending

The account was fully created, but not approved by an admin.

Active

The account is fully operational.

Locked

An admin has disabled the account.

Instances

Instances details
FromJSON AccountStatus Source # 
Instance details

Defined in Polysemy.Account.Data.AccountStatus

ToJSON AccountStatus Source # 
Instance details

Defined in Polysemy.Account.Data.AccountStatus

Generic AccountStatus Source # 
Instance details

Defined in Polysemy.Account.Data.AccountStatus

Associated Types

type Rep AccountStatus :: Type -> Type #

Show AccountStatus Source # 
Instance details

Defined in Polysemy.Account.Data.AccountStatus

Eq AccountStatus Source # 
Instance details

Defined in Polysemy.Account.Data.AccountStatus

type Rep AccountStatus Source # 
Instance details

Defined in Polysemy.Account.Data.AccountStatus

type Rep AccountStatus = D1 ('MetaData "AccountStatus" "Polysemy.Account.Data.AccountStatus" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'False) ((C1 ('MetaCons "Creating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pending" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Active" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Locked" 'PrefixI 'False) (U1 :: Type -> Type)))

data Privilege Source #

The stock privilege type, used only for admin endpoint authorization in polysemy-account-api.

Constructors

Web 
Api 
Admin 

Instances

Instances details
FromJSON Privilege Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

ToJSON Privilege Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

Generic Privilege Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

Associated Types

type Rep Privilege :: Type -> Type #

Show Privilege Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

Eq Privilege Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

Default [Privilege] Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

Methods

def :: [Privilege] #

type Rep Privilege Source # 
Instance details

Defined in Polysemy.Account.Data.Privilege

type Rep Privilege = D1 ('MetaData "Privilege" "Polysemy.Account.Data.Privilege" "polysemy-account-0.2.0.0-JBrIF35CBfcBfeWmsi0YZS" 'False) (C1 ('MetaCons "Web" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Api" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Admin" 'PrefixI 'False) (U1 :: Type -> Type)))

type AccountP = Account [Privilege] Source #

Convenience alias for using the default privilege type with Account.

type AuthedAccountP i = AuthedAccount i [Privilege] Source #

Convenience alias for using the default privilege type with AuthedAccount.

newtype AuthToken Source #

An auth token, used by the JWT tools in polysemy-account-api.

Constructors

AuthToken 

Fields

newtype Port Source #

An API port, used by the Servant tools in polysemy-account-api.

Constructors

Port Word 

Instances

Instances details
FromJSON Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

ToJSON Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Enum Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

succ :: Port -> Port #

pred :: Port -> Port #

toEnum :: Int -> Port #

fromEnum :: Port -> Int #

enumFrom :: Port -> [Port] #

enumFromThen :: Port -> Port -> [Port] #

enumFromTo :: Port -> Port -> [Port] #

enumFromThenTo :: Port -> Port -> Port -> [Port] #

Num Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

(+) :: Port -> Port -> Port #

(-) :: Port -> Port -> Port #

(*) :: Port -> Port -> Port #

negate :: Port -> Port #

abs :: Port -> Port #

signum :: Port -> Port #

fromInteger :: Integer -> Port #

Read Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Integral Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

quot :: Port -> Port -> Port #

rem :: Port -> Port -> Port #

div :: Port -> Port -> Port #

mod :: Port -> Port -> Port #

quotRem :: Port -> Port -> (Port, Port) #

divMod :: Port -> Port -> (Port, Port) #

toInteger :: Port -> Integer #

Real Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

toRational :: Port -> Rational #

Show Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Eq Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

(==) :: Port -> Port -> Bool #

(/=) :: Port -> Port -> Bool #

Ord Port Source # 
Instance details

Defined in Polysemy.Account.Data.Port

Methods

compare :: Port -> Port -> Ordering #

(<) :: Port -> Port -> Bool #

(<=) :: Port -> Port -> Bool #

(>) :: Port -> Port -> Bool #

(>=) :: Port -> Port -> Bool #

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #