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

Polysemy.Account.Api

Description

 
Synopsis

Effects

data Jwt a :: Effect Source #

Effect for managing JSON Web Token generation.

key :: forall a r. Member (Jwt a) r => Sem r JWK Source #

Generate a new JSON Web Key for signing tokens.

settings :: forall a r. Member (Jwt a) r => Sem r JWTSettings Source #

Obtain the settings used to sign and validate tokens.

makeToken :: forall a r. Member (Jwt a) r => a -> Sem r AuthToken Source #

Create a new JSON Web Token.

data GenJwk :: Effect Source #

Effect for generating JSON Web Keys.

genJwk :: forall r. Member GenJwk r => Sem r JWK Source #

Generate a JSON Web Key.

data Authorize i param priv :: Effect where Source #

This effect is used by the combinators in Polysemy.Account.Api.Server.AuthEndpoint to decide whether an account is authorized to access an endpoint.

The type parameters signify:

i
The storage ID type.
param
Identifies the authorization requirements of the endpoint.
priv
The privilege type stored in the database.

Constructors

Authorize :: param -> AuthedAccount i priv -> Authorize i param priv m (Maybe Text)

Decide whether the given account is authorized to use the endpoint characterized by the param. Return Just an error message if access is denied.

type AuthorizeP i = Authorize i [Privilege] [Privilege] Source #

Convenience alias for using the default privilege type with Authorize.

authorize :: forall i param priv r. Member (Authorize i param priv) r => param -> AuthedAccount i priv -> Sem r (Maybe Text) Source #

Decide whether the given account is authorized to use the endpoint characterized by the param. Return Just an error message if access is denied.

Interpreters

interpretJwt :: forall a r. Members [Error Text, Embed IO] r => ToJWT a => InterpreterFor (Jwt a) r Source #

Interpret Jwt by storing the key in AtomicState in memory.

interpretJwtDb :: forall a r. Members [Database !! DbError, Error InitDbError, Error Text, Log, Mask, Resource, Race, Embed IO] r => ToJWT a => InterpreterFor (Jwt a !! DbError) r Source #

Interpret Jwt using interpretJwtPersistent and interpret AtomicState as a PostgreSQL table using polysemy-hasql, generating the JWK when it is not found in the database.

interpretJwtPersistent :: forall a e r. Members [AtomicState JWK !! e, Error Text, Embed IO] r => ToJWT a => InterpreterFor (Jwt a !! e) r Source #

Interpret Jwt by storing the key in AtomicState, requiring the key to be present from the start. This is intended to be used with a database backing the AtomicState, the key being generated when starting the app.

Generates Ed25519 keys.

Errors originating from the token generator are critical.

interpretJwtState :: Members [GenJwk, AtomicState (Maybe JWK), Error Text, Embed IO] r => ToJWT a => InterpreterFor (Jwt a) r Source #

Interpret Jwt by storing the key in AtomicState, generating it on the fly if absent.

Generates Ed25519 keys.

Errors originating from the token generator are critical.

interpretAuthorizeWith :: (param -> AuthedAccount i priv -> Sem r (Maybe Text)) -> InterpreterFor (Authorize i param priv) r Source #

Interpret Authorize using a monadic predicate.

interpretAuthorizeP :: InterpreterFor (Authorize i [Privilege] [Privilege]) r Source #

Interpret Authorize using Privilege for both parameter and privilege types.

Simply verify that all parameter privileges are present in the account.

interpretAccountsDb :: forall p s r. Members [Database !! DbError, Id UUID, Log, Error InitDbError, Embed IO] r => Column p "privileges" s s => ReifyCodec FullCodec s p => ReifyDd s => CheckedProjection (DdAccount UUID p s) (DdAccount UUID p s) => Dd s -> AccountsConfig p -> InterpretersFor [Accounts UUID p !! AccountsError, Password] r Source #

Interpret Accounts and Password using PostgreSQL as storage backend.

interpretAccountStore :: forall i p s r. PrimColumn i => Column p "privileges" s s => ReifyCodec FullCodec s p => ReifyDd s => Dd s -> Member (StoreTable i (Account p) !! DbError) r => InterpreterFor (Store i (Account p) !! DbError) r Source #

Interpret Store for Account as a DbTable.

interpretAccountTable :: forall i p s r. PrimColumn i => Column p "privileges" s s => ReifyCodec FullCodec s p => ReifyDd s => Dd s -> Members [Database !! DbError, Log, Embed IO] r => InterpreterFor (StoreTable i (Account p) !! DbError) r Source #

Interpret DbTable for Account.

Servant

type Authed i p = Auth '[JWT] (AuthedAccount i p) #

A Servant API marker for JWT auth with AuthedAccount

type AccountApi i p = "account" :> ((Authed i p :> (Capture "id" i :> Get '[JSON] (Uid i (Account p)))) :<|> ((Authed i p :> Get '[JSON] [Uid i (Account p)]) :<|> ((Authed i p :> (ReqBody '[JSON] (Uid i (Account p)) :> Put '[JSON] NoContent)) :<|> (Authed i p :> (Capture "id" i :> (ReqBody '[JSON] (Account p) :> Put '[JSON] NoContent)))))) Source #

An internal API for accessing accounts.

type AuthApi i p = "auth" :> ((Authed i p :> Get '[JSON] (AuthedAccount i p)) :<|> (("login" :> (ReqBody '[JSON] AccountCredentials :> PostResetContent '[JSON] AuthToken)) :<|> ("register" :> (ReqBody '[JSON] AccountCredentials :> PostCreated '[JSON] AuthToken)))) Source #

An API allowing users to log in, register accounts, and authenticate with a JWT to obtain their account information.

accountServer :: forall i param p r. Show i => Show p => AuthEndpointParam param => Members [Authorize i param p, Accounts i p !! AccountsError, Log, Stop ServerError] r => ServerT (AccountApi i p) (Sem r) Source #

Handlers for AccountApi.

type AuthedP i = Authed i [Privilege] #

Convenience alias for using the default privilege type with Authed.

type AccountApiP i = AccountApi i [Privilege] Source #

Convenience alias for using the default privilege type with AccountApi.

type AuthApiP i = AuthApi i [Privilege] Source #

Convenience alias for using the default privilege type with AuthApi.

runServerJwt :: forall (api :: Type) a e r. ServerAuth api => Members [Sync ServerReady, Jwt a !! e, Log, Interrupt, Error Text, Final IO] r => ServerT api (Sem (Stop ServerError ': r)) -> Port -> Sem r () Source #

Run a Servant server with JSON Web Token authentication using settings from Jwt.

runServerJwtWith :: forall (api :: Type) (context :: [Type]) a e r. HasContextEntry (context .++ DefaultErrorFormatters) ErrorFormatters => HasServer api (AuthContext ++ context) => Members [Sync ServerReady, Jwt a !! e, Log, Interrupt, Error Text, Final IO] r => Context context -> ServerT api (Sem (Stop ServerError ': r)) -> Port -> Sem r () Source #

Run a Servant server with JSON Web Token authentication using settings from Jwt.

This variant allows supplying additional Contexts.

runServerSem :: forall (api :: Type) context r a. HasServer api context => HasContextEntry (context .++ DefaultErrorFormatters) ErrorFormatters => Members [Log, Embed IO, Final IO] r => ServerT api (Sem (Stop ServerError ': r)) -> Context context -> (Application -> IO a) -> Sem r a Source #

Run a Servant server using a callback in Final IO, sending logs to Log.

data ServerReady Source #

A dummy value used to indicate that the server has fully started up, using Sync.

Constructors

ServerReady 

Instances

Instances details
Show ServerReady Source # 
Instance details

Defined in Polysemy.Account.Api.NativeContext

Eq ServerReady Source # 
Instance details

Defined in Polysemy.Account.Api.NativeContext

authorizeEndpoint :: forall i param p r a. Show (AuthedAccount i p) => AuthEndpoint i param p r => param -> (AuthedAccount i p -> Sem r a) -> AuthResult (AuthedAccount i p) -> Sem r a Source #

Wrap an authenticated handler function with an authorization check.

Sends the account information and given endpoint param to the Authorize effect if the authentication material is valid.

class AuthEndpointParam param where Source #

Basic values for describing the requirements of an endpoint for either "any user" or "admin".

accountOnly :: forall i param p r a. Show (AuthedAccount i p) => AuthEndpoint i param p r => (AuthedAccount i p -> Sem r a) -> AuthResult (AuthedAccount i p) -> Sem r a Source #

Require that the authentication material belongs to an active account.

accountOnly_ :: forall i param p r a. Show (AuthedAccount i p) => AuthEndpoint i param p r => Sem r a -> AuthResult (AuthedAccount i p) -> Sem r a Source #

Require that the authentication material belongs to an active account.

accountOnly1 :: forall i param p r a b. Show (AuthedAccount i p) => AuthEndpoint i param p r => (AuthedAccount i p -> a -> Sem r b) -> AuthResult (AuthedAccount i p) -> a -> Sem r b Source #

Require that the authentication material belongs to an active account.

accountOnly1_ :: forall i param p r a b. Show (AuthedAccount i p) => AuthEndpoint i param p r => (a -> Sem r b) -> AuthResult (AuthedAccount i p) -> a -> Sem r b Source #

Require that the authentication material belongs to an active account.

accountOnly2 :: forall i param p r a b c. Show (AuthedAccount i p) => AuthEndpoint i param p r => (AuthedAccount i p -> a -> b -> Sem r c) -> AuthResult (AuthedAccount i p) -> a -> b -> Sem r c Source #

Require that the authentication material belongs to an active account.

accountOnly2_ :: forall i param p r a b c. Show (AuthedAccount i p) => AuthEndpoint i param p r => (a -> b -> Sem r c) -> AuthResult (AuthedAccount i p) -> a -> b -> Sem r c Source #

Require that the authentication material belongs to an active account.

adminOnly :: forall i param p r a. Show (AuthedAccount i p) => AuthEndpoint i param p r => (AuthedAccount i p -> Sem r a) -> AuthResult (AuthedAccount i p) -> Sem r a Source #

Require that the authentication material belongs to an active admin account.

adminOnly_ :: forall i param p r a. Show (AuthedAccount i p) => AuthEndpoint i param p r => Sem r a -> AuthResult (AuthedAccount i p) -> Sem r a Source #

Require that the authentication material belongs to an active admin account.

adminOnly1 :: forall i param p r a b. Show (AuthedAccount i p) => AuthEndpoint i param p r => (AuthedAccount i p -> a -> Sem r b) -> AuthResult (AuthedAccount i p) -> a -> Sem r b Source #

Require that the authentication material belongs to an active admin account.

adminOnly1_ :: forall i param p r a b. Show (AuthedAccount i p) => AuthEndpoint i param p r => (a -> Sem r b) -> AuthResult (AuthedAccount i p) -> a -> Sem r b Source #

Require that the authentication material belongs to an active admin account.

adminOnly2 :: forall i param p r a b c. Show (AuthedAccount i p) => AuthEndpoint i param p r => (AuthedAccount i p -> a -> b -> Sem r c) -> AuthResult (AuthedAccount i p) -> a -> b -> Sem r c Source #

Require that the authentication material belongs to an active admin account.

adminOnly2_ :: forall i param p r a b c. Show (AuthedAccount i p) => AuthEndpoint i param p r => (a -> b -> Sem r c) -> AuthResult (AuthedAccount i p) -> a -> b -> Sem r c Source #

Require that the authentication material belongs to an active admin account.