| Copyright | (c) 2016 Al Zohali |
|---|---|
| License | BSD3 |
| Maintainer | Al Zohali <zohl@fmap.me> |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
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.
- type CipherAlgorithm c = c -> IV c -> ByteString -> ByteString
- type family AuthCookieData
- data Cookie = Cookie {}
- data AuthCookieException
- data WithMetadata a = WithMetadata {}
- type Cookied a = Headers '[Header "Set-Cookie" EncryptedSession] a
- cookied :: (Serialize a, ServerKeySet k) => AuthCookieSettings -> RandomSource -> k -> (a -> r) -> WithMetadata a -> Handler (Cookied r)
- data RandomSource
- mkRandomSource :: (MonadIO m, DRG d) => IO d -> Int -> m RandomSource
- getRandomBytes :: MonadIO m => RandomSource -> Int -> m ByteString
- generateRandomBytes :: Int -> IO ByteString
- type ServerKey = ByteString
- class ServerKeySet k where
- data PersistentServerKey
- mkPersistentServerKey :: ByteString -> PersistentServerKey
- data RenewableKeySet s p
- data RenewableKeySetHooks s p = RenewableKeySetHooks {
- rkshNewState :: forall m. (MonadIO m, MonadThrow m) => p -> ([ServerKey], s) -> m ([ServerKey], s)
- rkshNeedUpdate :: forall m. (MonadIO m, MonadThrow m) => p -> ([ServerKey], s) -> m Bool
- rkshRemoveKey :: forall m. (MonadIO m, MonadThrow m) => p -> ServerKey -> m ()
- mkRenewableKeySet :: MonadIO m => RenewableKeySetHooks s p -> p -> s -> m (RenewableKeySet s p)
- data AuthCookieSettings where
- AuthCookieSettings :: (HashAlgorithm h, BlockCipher c) => {..} -> AuthCookieSettings
- newtype EncryptedSession = EncryptedSession ByteString
- emptyEncryptedSession :: EncryptedSession
- encryptCookie :: (MonadIO m, MonadThrow m, ServerKeySet k) => AuthCookieSettings -> k -> Cookie -> m (Tagged EncryptedCookie ByteString)
- decryptCookie :: (MonadIO m, MonadThrow m, ServerKeySet k) => AuthCookieSettings -> k -> Tagged EncryptedCookie ByteString -> m (WithMetadata Cookie)
- encryptSession :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> RandomSource -> k -> a -> m (Tagged SerializedEncryptedCookie ByteString)
- decryptSession :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> k -> Tagged SerializedEncryptedCookie ByteString -> m (WithMetadata a)
- addSession :: (MonadIO m, MonadThrow m, Serialize a, AddHeader (e :: Symbol) EncryptedSession s r, ServerKeySet k) => AuthCookieSettings -> RandomSource -> k -> a -> s -> m r
- removeSession :: (Monad m, AddHeader (e :: Symbol) EncryptedSession s r) => AuthCookieSettings -> s -> m r
- addSessionToErr :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> RandomSource -> k -> a -> ServantErr -> m ServantErr
- removeSessionFromErr :: Monad m => AuthCookieSettings -> ServantErr -> m ServantErr
- getSession :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> k -> Request -> m (Maybe (WithMetadata a))
- defaultAuthHandler :: (Serialize a, ServerKeySet k) => AuthCookieSettings -> k -> AuthHandler Request (WithMetadata a)
- renderSession :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> RandomSource -> k -> a -> m ByteString
- parseSessionRequest :: AuthCookieSettings -> RequestHeaders -> Maybe (Tagged SerializedEncryptedCookie ByteString)
- parseSessionResponse :: AuthCookieSettings -> ResponseHeaders -> Maybe (Tagged SerializedEncryptedCookie ByteString)
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.
Cookie representation.
Constructors
| Cookie | |
Fields
| |
data AuthCookieException Source #
The exception is thrown when something goes wrong with this package.
Constructors
| CannotMakeIV ByteString | Could not make |
| 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. |
| CannotParseExpirationTime ByteString | Thrown when expiration time cannot be parsed. |
| CookieExpired UTCTime UTCTime | Thrown when |
| SessionDeserializationFailed String |
data WithMetadata a Source #
Wrapper for cookies and sessions to keep some related metadata.
Constructors
| WithMetadata | |
type Cookied a = Headers '[Header "Set-Cookie" EncryptedSession] a Source #
Helper type to wrap endpoints.
Arguments
| :: (Serialize a, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> RandomSource | Random source to use |
| -> k | Instance of |
| -> (a -> r) | Implementation of an endpoint |
| -> WithMetadata a -> Handler (Cookied r) | Cookied endpoint |
Wrapper for an implementation of an endpoint to make it automatically renew the cookies.
data RandomSource Source #
A wrapper of self-resetting DRG suitable for concurrent usage.
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 |
Constructor for RandomSource value.
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 |
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.
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.
Instances
| ServerKeySet PersistentServerKey Source # | |
| Eq s => ServerKeySet (RenewableKeySet s p) Source # | |
mkPersistentServerKey :: ByteString -> PersistentServerKey Source #
Create instance of PersistentServerKey.
data RenewableKeySet s p Source #
Customizable key set, that provides partial implementation of
ServerKeySet.
Instances
| Eq s => ServerKeySet (RenewableKeySet s p) Source # | |
data RenewableKeySetHooks s p Source #
Customizable actions for RenewableKeySet.
Constructors
| RenewableKeySetHooks | |
Fields
| |
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
| |
Instances
newtype EncryptedSession Source #
A newtype wrapper over ByteString
Constructors
| EncryptedSession ByteString |
emptyEncryptedSession :: EncryptedSession Source #
An empty EncryptedSession
Arguments
| :: (MonadIO m, MonadThrow m, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> k | Instance of |
| -> Cookie | The |
| -> m (Tagged EncryptedCookie ByteString) | Encrypted |
Encrypt given Cookie with server key.
The function can throw the following exceptions (of type
AuthCookieException):
Arguments
| :: (MonadIO m, MonadThrow m, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> k | Instance of |
| -> Tagged EncryptedCookie ByteString | The |
| -> m (WithMetadata Cookie) | The decrypted |
Decrypt a Cookie from ByteString.
The function can throw the following exceptions (of type
AuthCookieException):
Arguments
| :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> RandomSource | Random source to use |
| -> k | Instance of |
| -> a | Session value |
| -> m (Tagged SerializedEncryptedCookie ByteString) | Serialized and encrypted session |
Pack session object into a cookie. The function can throw the same
exceptions as encryptCookie.
Arguments
| :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> k | Instance of |
| -> Tagged SerializedEncryptedCookie ByteString | Cookie in binary form |
| -> m (WithMetadata a) | Unpacked session value |
Unpack session value from a cookie. The function can throw the same
exceptions as decryptCookie.
Arguments
| :: (MonadIO m, MonadThrow m, Serialize a, AddHeader (e :: Symbol) EncryptedSession s r, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> RandomSource | Random source to use |
| -> k | Instance of |
| -> a | The session value |
| -> s | Response to add session to |
| -> m r | Response with the session added |
Add cookie header to response. The function can throw the same
exceptions as encryptSession.
Arguments
| :: (Monad m, AddHeader (e :: Symbol) EncryptedSession s r) | |
| => AuthCookieSettings | Options, see |
| -> s | Response to return with session removed |
| -> m r | Response with the session "removed" |
Remove a session by invalidating the cookie.
Arguments
| :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> RandomSource | Random source to use |
| -> k | Instance of |
| -> a | The session value |
| -> ServantErr | Servant error to add the cookie to |
| -> m ServantErr |
Add cookie session to error allowing to set cookie even if response is not 200.
Arguments
| :: Monad m | |
| => AuthCookieSettings | Options, see |
| -> ServantErr | Servant error to add the cookie to |
| -> m ServantErr |
Remove a session by invalidating the cookie. Cookie expiry date is set at 0 and content is wiped
Arguments
| :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> k |
|
| -> Request | The request |
| -> m (Maybe (WithMetadata 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.
Arguments
| :: (Serialize a, ServerKeySet k) | |
| => AuthCookieSettings | Options, see |
| -> k | Instance of |
| -> AuthHandler Request (WithMetadata a) | The result |
Cookie authentication handler.
renderSession :: (MonadIO m, MonadThrow m, Serialize a, ServerKeySet k) => AuthCookieSettings -> RandomSource -> k -> a -> m ByteString Source #
Render session cookie to ByteString.
parseSessionRequest :: AuthCookieSettings -> RequestHeaders -> Maybe (Tagged SerializedEncryptedCookie ByteString) Source #
Parse session cookie from RequestHeaders.
parseSessionResponse :: AuthCookieSettings -> ResponseHeaders -> Maybe (Tagged SerializedEncryptedCookie ByteString) Source #
Parse session cookie from ResponseHeaders.