hsoz-0.0.1.0: Iron, Hawk, Oz: Web auth protocols

Safe HaskellNone
LanguageHaskell2010

Network.Hawk.Server

Contents

Description

These are functions for checking authenticated requests and sending authenticated responses.

For an easy way to add Hawk authentication to a Network.Wai Application, use the Network.Hawk.Middleware module.

Synopsis

Authenticating Network.Wai requests

authenticateRequest :: MonadIO m => AuthReqOpts -> CredentialsFunc m t -> Request -> Maybe ByteString -> m (AuthResult t) Source #

Checks the Authorization header of a Request and (optionally) a payload. The header will be parsed and verified with the credentials supplied.

If the request payload is provided, it will be verified. If a payload is not supplied, it can be verified later with authenticatePayload.

authenticatePayload :: AuthSuccess t -> PayloadInfo -> Either String () Source #

Verifies the payload hash as a separate step after other things have been check. This is useful when the request body is streamed for example.

authenticateBewitRequest :: MonadIO m => AuthReqOpts -> CredentialsFunc m t -> Request -> m (AuthResult t) Source #

Checks the Authorization header of a Request according to the "bewit" scheme. See Network.Hawk.URI for a description of that scheme.

data AuthReqOpts Source #

Bundle of parameters for authenticateRequest. Provides information about what the public URL of the server would be. If the application is served from a HTTP reverse proxy, then the Host header might have a different name, or the hostname:port might need to be overridden.

Constructors

AuthReqOpts 

Fields

Instances

Generic variants

authenticate :: MonadIO m => AuthOpts -> CredentialsFunc m t -> HawkReq -> m (AuthResult t) Source #

Checks the Authorization header of a generic request. The header will be parsed and verified with the credentials supplied.

If a payload is provided, it will be verified. If the payload is not supplied, it can be verified later with authenticatePayload.

authenticateBewit :: MonadIO m => AuthOpts -> CredentialsFunc m t -> HawkReq -> m (AuthResult t) Source #

Checks the Authorization header of a request (HawkReq) according to the "bewit" scheme.

authenticateMessage Source #

Arguments

:: MonadIO m 
=> AuthOpts

Options for verification.

-> CredentialsFunc m t

Credentials lookup function.

-> ByteString

Destination host.

-> Maybe Int

Destination port.

-> ByteString

The message.

-> MessageAuth

Signed message object.

-> m (AuthResult t) 

Verifies message signature with the given credentials and authorization attributes.

data HawkReq Source #

A package of values containing the attributes of a HTTP request which are relevant to Hawk authentication.

Options for authentication

data AuthOpts Source #

Bundle of parameters for authenticate.

Constructors

AuthOpts 

Fields

Instances

data Credentials Source #

The set of data the server requires for key-based hash verification of artifacts.

Constructors

Credentials 

Fields

Instances

Eq Credentials Source # 
Show Credentials Source # 
Generic Credentials Source # 

Associated Types

type Rep Credentials :: * -> * #

type Rep Credentials Source # 
type Rep Credentials = D1 (MetaData "Credentials" "Network.Hawk.Internal.Server.Types" "hsoz-0.0.1.0-5r17DkUA43zE9P6QhuhthQ" False) (C1 (MetaCons "Credentials" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "scKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Key)) (S1 (MetaSel (Just Symbol "scAlgorithm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HawkAlgo))))

type CredentialsFunc m t = ClientId -> m (Either String (Credentials, t)) Source #

A user-supplied callback to get credentials from a client identifier.

type NonceFunc = Key -> POSIXTime -> Nonce -> IO Bool Source #

User-supplied nonce validation function. It should return True if the nonce is valid.

Checking nonces can prevent request replay attacks. If the same key and nonce have already been seen, then the request can be denied.

type Nonce = ByteString Source #

The nonce should be a short sequence of random ASCII characters.

def :: Default a => a #

The default value for this type.

Authentication result

type AuthResult t = AuthResult' (AuthSuccess t) Source #

The end result of authentication.

type AuthResult' r = Either AuthFail r Source #

An intermediate result of authentication.

data AuthSuccess t Source #

Successful authentication produces a set of credentials and "artifacts". Also included in the result is the result of CredentialsFunc.

Instances

data AuthFail Source #

Authentication can fail in multiple ways. This type includes the information necessary to generate a suitable response for the client. In the case of a stale timestamp, the client may try another authenticated request.

authValue :: AuthSuccess t -> t Source #

The result of an AuthSuccess.

authFailMessage :: AuthFail -> String Source #

The error message from an AuthFail.

Authenticated reponses

header :: AuthResult t -> Maybe PayloadInfo -> (Status, Header) Source #

Generates a suitable Server-Authorization header to send back to the client. Credentials and artifacts would be provided by a previous call to authenticateRequest (or authenticate).

If a payload is supplied, its hash will be included in the header.