servant-auth-cookie-0.6.0: Authentication via encrypted cookies

Copyright(c) 2016 Al Zohali
LicenseBSD3
MaintainerAl Zohali <zohl@fmap.me>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Servant.Server.Experimental.Auth.Cookie

Description

Description

Authentication via encrypted client-side cookies, inspired by client-session library by Michael Snoyman and based on ideas of the paper "A Secure Cookie Protocol" by Alex Liu et al.

Synopsis

Documentation

type CipherAlgorithm c = c -> IV c -> ByteString -> ByteString Source #

A type for encryption and decryption functions operating on ByteStrings.

type family AuthCookieData Source #

A type family that maps user-defined data to AuthServerData.

data AuthCookieException Source #

The exception is thrown when something goes wrong with this package.

Constructors

CannotMakeIV ByteString

Could not make IV for block cipher.

BadProperKey CryptoError

Could not initialize a cipher context.

TooShortProperKey Int Int

The key is too short for current cipher algorithm. Arguments of this constructor: minimal key length, actual key length.

IncorrectMAC ByteString

Thrown when Message Authentication Code (MAC) is not correct.

CookieExpired UTCTime UTCTime

Thrown when Cookie has expired. Arguments of the constructor: expiration time, actual time.

SessionDeserializationFailed String

This is thrown when runGet or decode blows up.

type AuthCookieExceptionHandler = forall a. AuthCookieException -> Handler (Maybe (ExtendedPayloadWrapper a)) Source #

Type for exception handler.

type AuthCookieHandler a Source #

Arguments

 = ServerKeySet k 
=> AuthCookieSettings

Options, see AuthCookieSettings

-> k

Instance of ServerKeySet to use

-> AuthHandler Request (ExtendedPayloadWrapper a)

The result

Type for cookied handler.

data PayloadWrapper a Source #

Wrapper for session value that goes into cookies' payload.

Instances

Generic (PayloadWrapper a) Source # 

Associated Types

type Rep (PayloadWrapper a) :: * -> * #

Serialize a => Serialize (PayloadWrapper a) Source # 
type Rep (PayloadWrapper a) Source # 
type Rep (PayloadWrapper a) = D1 (MetaData "PayloadWrapper" "Servant.Server.Experimental.Auth.Cookie" "servant-auth-cookie-0.6.0-1Iu8dtw7QNMD6YVqtc0Cd9" False) (C1 (MetaCons "PayloadWrapper" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pwSession") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) ((:*:) (S1 (MetaSel (Just Symbol "pwSettings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SessionSettings)) (S1 (MetaSel (Just Symbol "pwExpiration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))))

data ExtendedPayloadWrapper a Source #

Wrapper for session value with metadata that doesn't go into payload.

type Cookied a = Headers '[Header "Set-Cookie" EncryptedSession] a Source #

Helper type to wrap endpoints.

type CookiedWrapper c = forall f r. CookiedWrapperClass f r c => f -> r Source #

Type for curried cookied function (with fixed settings, random source, keyset and session type).

class CookiedWrapperClass f r c where Source #

Class of functions that can be wrapped with cookied.

Minimal complete definition

wrapCookied

Instances

Serialize c => CookiedWrapperClass (Handler b) (Handler (Cookied b)) c Source # 

Methods

wrapCookied :: ServerKeySet k => (AuthCookieSettings, RandomSource, k, Proxy * c) -> Maybe (PayloadWrapper c) -> Handler b -> Handler (Cookied b) Source #

(Serialize c, CookiedWrapperClass b b' c) => CookiedWrapperClass (a -> b) (a -> b') c Source # 

Methods

wrapCookied :: ServerKeySet k => (AuthCookieSettings, RandomSource, k, Proxy * c) -> Maybe (PayloadWrapper c) -> (a -> b) -> a -> b' Source #

(Serialize c, CookiedWrapperClass b b' c) => CookiedWrapperClass (c -> b) (ExtendedPayloadWrapper c -> b') c Source # 

cookied Source #

Arguments

:: (ServerKeySet k, Serialize c) 
=> AuthCookieSettings

Options, see AuthCookieSettings

-> RandomSource

Random source to use

-> k

Instance of ServerKeySet to use

-> Proxy c

Type of session

-> CookiedWrapper c

Wrapper that transforms given functions.

Wrapper for endpoints that use cookies. It transforms function of type: >>> q1 -> q2 -> ... -> Session -> ... -> qN -> Handler r into >>> q1 -> q2 -> ... -> ExtendedPayloadWrapper Session -> ... qN -> Handler (Cookied r)

Non-session variables number can be arbitrary. It supposed to be used in tandem with Cookied type.

Using this wrapper requires FlexibleContexts extention to be turned on. In case of curring cookied function, it's highly recommended to provide signature for this (see CookiedWrapper).

data RandomSource Source #

A wrapper of self-resetting DRG suitable for concurrent usage.

mkRandomSource Source #

Arguments

:: (MonadIO m, DRG d) 
=> IO d

How to get deterministic random generator

-> Int

Threshold (number of bytes to be generated before resetting)

-> m RandomSource

New RandomSource value

Constructor for RandomSource value.

getRandomBytes Source #

Arguments

:: MonadIO m 
=> RandomSource

The source of random numbers

-> Int

How many random bytes to generate

-> m ByteString

The generated bytes in form of a ByteString

Extract pseudo-random bytes from RandomSource.

generateRandomBytes :: Int -> IO ByteString Source #

Generates random sequence of bytes from new DRG

type ServerKey = ByteString Source #

Internal representation of a server key.

class ServerKeySet k where Source #

Interface for a set of server keys.

Minimal complete definition

getKeys, removeKey

Methods

getKeys :: (MonadThrow m, MonadIO m) => k -> m (ServerKey, [ServerKey]) Source #

Retrieve current and rotated keys respectively.

removeKey :: (MonadThrow m, MonadIO m) => k -> ServerKey -> m () Source #

Non-graciously remove the key from a keyset.

data PersistentServerKey Source #

A keyset containing only one key, that doesn't change.

data RenewableKeySet s p Source #

Customizable key set, that provides partial implementation of ServerKeySet.

data RenewableKeySetHooks s p Source #

Customizable actions for RenewableKeySet.

Constructors

RenewableKeySetHooks 

Fields

  • rkshNewState :: forall m. (MonadIO m, MonadThrow m) => p -> ([ServerKey], s) -> m ([ServerKey], s)

    Called when a keyset needs to refresh it's state. It's result might be discarded occasionally in favour of result yielded in another thread.

  • rkshNeedUpdate :: forall m. (MonadIO m, MonadThrow m) => p -> ([ServerKey], s) -> m Bool

    Called before retrieving the keys and refreshing the state.

  • rkshRemoveKey :: forall m. (MonadIO m, MonadThrow m) => p -> ServerKey -> m ()

    Called after removing the key. This hook is called only if the key belongs to a keyset and called once per key. The only purpose of it is to clear the garbage after removing the key. The state might differs after removing the key and before calling the hook, therefore the hook doesn't rely on the state.

mkRenewableKeySet Source #

Arguments

:: MonadIO m 
=> RenewableKeySetHooks s p

Hooks

-> p

Parameters

-> s

Initial state

-> m (RenewableKeySet s p) 

Create instance of RenewableKeySet.

data AuthCookieSettings where Source #

Options that determine authentication mechanisms. Use def to get default value of this type.

Constructors

AuthCookieSettings :: (HashAlgorithm h, BlockCipher c) => {..} -> AuthCookieSettings 

Fields

data SessionSettings Source #

Options that determine session mechanisms. Use def to get default value of this type.

Constructors

SessionSettings 

Fields

data ExpirationType Source #

How to represent expiration to the client's browser.

Constructors

Expires

cookies will be provided with Expires flag. Deprecated in favour of 'Max-Age'.

MaxAge

cookies will be provided with 'Max-Age' flag. Doesn't work with older versions of IE.

Session

cookies will be removed when the user closes the browser.

Instances

Eq ExpirationType Source # 
Show ExpirationType Source # 
Generic ExpirationType Source # 

Associated Types

type Rep ExpirationType :: * -> * #

Serialize ExpirationType Source # 
Default ExpirationType Source # 

Methods

def :: ExpirationType #

type Rep ExpirationType Source # 
type Rep ExpirationType = D1 (MetaData "ExpirationType" "Servant.Server.Experimental.Auth.Cookie" "servant-auth-cookie-0.6.0-1Iu8dtw7QNMD6YVqtc0Cd9" False) ((:+:) (C1 (MetaCons "Expires" PrefixI False) U1) ((:+:) (C1 (MetaCons "MaxAge" PrefixI False) U1) (C1 (MetaCons "Session" PrefixI False) U1)))

encryptSession Source #

Arguments

:: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) 
=> AuthCookieSettings

Options, see AuthCookieSettings

-> RandomSource

Random source to use

-> k

Instance of ServerKeySet to use

-> SessionSettings

Session settings

-> a

Session value

-> m (Tagged SerializedEncryptedCookie ByteString)

Serialized and encrypted session

Pack session object into a cookie.

The function can throw the following exceptions (of type AuthCookieException):

decryptSession Source #

Arguments

:: (MonadIO m, MonadThrow m, ServerKeySet k, Serialize a) 
=> AuthCookieSettings

Options, see AuthCookieSettings

-> k

Instance of ServerKeySet to use

-> Tagged SerializedEncryptedCookie ByteString

The ByteString to decrypt

-> m (ExtendedPayloadWrapper a)

The decrypted Cookie

Unpack session value from a cookie. The function can throw the same exceptions as decryptCookie.

The function can throw the following exceptions (of type AuthCookieException):

addSession :: AddHeader (e :: Symbol) EncryptedSession r s => AddSession r s Source #

Add cookie header to response. The function can throw the same exceptions as encryptSession.

removeSession :: AddHeader (e :: Symbol) EncryptedSession r s => RemoveSession r s Source #

Remove a session by invalidating the cookie.

addSessionToErr :: AddSession ServantErr ServantErr Source #

Add cookie session to error allowing to set cookie even if response is not 200.

removeSessionFromErr :: RemoveSession ServantErr ServantErr Source #

Remove a session by invalidating the cookie. Cookie expiry date is set at 0 and content is wiped

getSession Source #

Arguments

:: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) 
=> AuthCookieSettings

Options, see AuthCookieSettings

-> k

ServerKeySet to use

-> Request

The request

-> m (Maybe (ExtendedPayloadWrapper a))

The result

Request handler that checks cookies. If Cookie is just missing, you get Nothing, but if something is wrong with its format, getSession can throw the same exceptions as decryptSession.

getHeaderSession :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> k -> Text -> m (Maybe (ExtendedPayloadWrapper a)) Source #

Get session from `Header "cookie" ByteString` in a route. Useful for checking authentication without denying access to route.

If Cookie is missing, you get Nothing, but but if something is wrong with its format, getSession can throw the same exceptions as decryptSession.

defaultAuthHandler :: Serialize a => AuthCookieHandler a Source #

Cookie authentication handler.

data SerializedEncryptedCookie Source #

Tag for base64 serialized and encrypted cookie.

data EncryptedCookie Source #

Tag for encrypted cookie.

data IVBytes Source #

Tag for IV bytes.

data PayloadBytes Source #

Tag for encrypted or raw payload bytes.

data PaddingBytes Source #

Tag for pading bytes.

data MACBytes Source #

Tag for MAC of a cookie.

cerealDecode :: (Serialize a, MonadThrow m) => Tagged b ByteString -> m a Source #

Wrapper for decode.

renderSession :: AddSession () ByteString Source #

Render session cookie to ByteString.

unProxy :: Proxy a -> a Source #

Return bottom of type provided as Proxy tag.

mkCookieKey :: (MonadThrow m, HashAlgorithm h, BlockCipher c) => Proxy c -> Proxy h -> Tagged ServerKeyBytes ByteString -> Tagged IVBytes ByteString -> m (Tagged CookieKeyBytes ByteString) Source #

Derives key for a cookie based on server key and IV.

mkPadding :: (MonadIO m, BlockCipher c) => RandomSource -> Proxy c -> Tagged PayloadBytes ByteString -> m (Tagged PaddingBytes ByteString) Source #

Generates padding of random bytes to align payload's length.

mkMAC :: HashAlgorithm h => Proxy h -> Tagged ServerKeyBytes ByteString -> Cookie -> Tagged MACBytes ByteString Source #

Generates cookie's signature.

applyCipherAlgorithm :: forall c m. (BlockCipher c, MonadThrow m) => CipherAlgorithm c -> Tagged IVBytes ByteString -> Tagged CookieKeyBytes ByteString -> Tagged PayloadBytes ByteString -> m (Tagged PayloadBytes ByteString) Source #

Applies given encryption or decryption algorithm to given data.