wai-hmac-auth-1.0.0: hmac authentication tools for WAI apps

Safe HaskellNone
LanguageHaskell2010

Network.Wai.Auth.HMAC

Contents

Description

you should only need the contents of the types and tools sections, but all the functions in this module are exported just in case.

Synopsis

types

newtype ApiKey Source

a newtype wrapper for api keys

Constructors

ApiKey ByteString 

Instances

newtype SecretKey Source

newtype wrapper for secret keys

Constructors

SecretKey ByteString 

data ApiKeySpec Source

specification for how the api key should be found in the request

Constructors

QueryParamKey ByteString

look for a query parameter with the specified name

HeaderKey HeaderName

look for the header with this name

data RequestConfig alg Source

request configuration specifies how to perform hmac signing and authentication on the request - i.e. where the api key will be found, where the timestamp is stored, how the signature is added to the request, and the hash algorithm to use.

Instances

Eq alg => Eq (RequestConfig alg) 
Show alg => Show (RequestConfig alg) 

data AuthFailure Source

all of the way that signing or authentication can fail.

Constructors

MissingApiKey ApiKeySpec

the request does not have an api key value that fits the spec

MissingTimestampHeader HeaderName

the request does not have a timestamp header

MissingSignatureHeader HeaderName

the request does not have a signature header (authenticate only)

SignatureBase64DecodeFailed String

the signature was not url-safe base 64 encoded properly (authenticate only)

SignatureToDigestFailed

the signature was not a properly encoded hash digest (e.g. for the hash algorithm being used) (authenticate only)

HashMismatch

the signature generated from the request did not match the signature contained within the reqest (authenticate only)

default setup

defaultRequestConfig :: RequestConfig SHA256 Source

default request configuration

defaultRequestConfig = RequestConfig defaultApiKeySpec "x-auth-timestamp" "x-auth-signature" SHA256

defaultApiKeySpec :: ApiKeySpec Source

default spec for getting the api key

defaultApiKeySpec = QueryParamKey "apiKey"

the tools

getApiKey :: ApiKeySpec -> Request -> Maybe ApiKey Source

use this to get the api key from the request according to spec

authenticate :: HashAlgorithm alg => RequestConfig alg -> Request -> SecretKey -> IO (Either AuthFailure Request) Source

authenticate the request according to the configuration and secret key. if it succeeds, produces a request with a requestBody that will produce the same chunk sequence as the original. if it fails, it will explain why.

signRequest :: HashAlgorithm alg => RequestConfig alg -> Request -> SecretKey -> IO (Either AuthFailure Request) Source

signs a request in accordance with the config. mostly for testing.

internals

checkRequestHmac :: (MonadIO m, HasReqConf alg m, AuthErrorsM m) => Request -> SecretKey -> m Request Source

the operation performed by authenticate

addSignatureToRequest :: (MonadIO m, HasReqConf alg m, AuthErrorsM m) => Request -> SecretKey -> m Request Source

the operation performed by signRequest

constraint aliases

type HasReqConf alg m = (HashAlgorithm alg, MonadReader (RequestConfig alg) m, Functor m) Source

a constraint alias for functions that need to access request configuration

type AuthErrorsM m = MonadError AuthFailure m Source

a constrain alias for functions that can fail

type WriteChunks m = MonadWriter (Seq ByteString) m Source

a constraint alias for functions that save chunks of the request body

type HmacState alg m = (Functor m, Applicative m, HashAlgorithm alg, MonadState (HMACContext alg) m) Source

a constrain alias for functions that perform incremental updates to the hash value

manipulate the request

rerunRequestBody :: (Functor m, MonadIO m) => Request -> Seq ByteString -> m Request Source

constructs a new request with a requestBody function that will produce each item in the input sequence until the sequence is empty.

setRequestBody :: Request -> IO ByteString -> Request Source

sets the request body to the IO action.

produceChunked :: Monoid a => IORef (Seq a) -> IO a Source

gets the next chunk from the referenced sequence, returning mempty if it is already empty. (if it is not, then the IORef is updated to point to the next item in the sequence).

addHeader :: Request -> (HeaderName, ByteString) -> Request Source

add a header to a request (without checking for pre-existing headers)

computing the request signature

hmacRequest :: (MonadIO m, HasReqConf alg m, AuthErrorsM m, WriteChunks m) => Request -> SecretKey -> m (HMAC alg) Source

performs the full incremental hash/sign algorithm on the request and returns the signature.

hmacRequestInit :: HasReqConf alg m => SecretKey -> m (HMACContext alg) Source

sets up the hash algorithm with the secret key

adding stuff to the hash

addHashComponents :: (MonadIO m, HasReqConf alg m, AuthErrorsM m, WriteChunks m, HmacState alg m) => Request -> m () Source

add all of the important components of the request to the hash

  • request method (newline)
  • timestamp header (newline)
  • api key (if necessary)
  • raw path info
  • query params (with a question mark to separate from the path info)
  • (newline)
  • the body of the request

ensureApiKeyIsAdded :: (AuthErrorsM m, HasReqConf alg m, HmacState alg m) => Request -> m () Source

ensure the hash/signature will include the api key value according to the spec - i.e. in either spec, this will fail the computation if the key is not present according to spec; this function will have no further effect for a query parameter key, but for a header key, it will add it to the hash.

addBodyToHash :: (MonadIO m, HmacState alg m, WriteChunks m) => Request -> m () Source

keep getting chunks from the request and appending them to the hash (and also storing them in the writer value) until there are no more chunks

getNextChunkForHash :: (MonadIO m, Functor m) => Request -> m (Maybe ByteString) Source

get the next chunk from the request body, if there is one

addToHash :: HmacState alg m => ByteString -> m () Source

add a value to the incremental hash

getting headers

getBase64DecodedSignature :: (HasReqConf alg m, AuthErrorsM m) => Request -> m (HMAC alg) Source

get the signature header value, decode it from base64 url encoding, and then read it as a digest

getTimestampHeader :: (AuthErrorsM m, HasReqConf alg m) => Request -> m ByteString Source

get the header that should contain the timestamp

getSignatureHeader :: (AuthErrorsM m, HasReqConf alg m) => Request -> m ByteString Source

get the header that should contain the signature

getHeader :: (AuthErrorsM m, HasReqConf alg m) => (RequestConfig alg -> HeaderName) -> (HeaderName -> AuthFailure) -> Request -> m ByteString Source

get a header from the request; throw an error if it can't be found

utility functions

justWhen :: (a -> Bool) -> a -> Maybe a Source

return the value if the predicate of it is true

justUnless :: (a -> Bool) -> a -> Maybe a Source

return the value if the predicate of it is false

allRead :: (Applicative m, Foldable t) => t (a -> m b) -> a -> m () Source

calls every function in the data structure, and then traverses/folds the contained actions.