mqtt-0.1.1.0: An MQTT protocol implementation.

Copyright(c) Lars Petersen 2016
LicenseMIT
Maintainerinfo@lars-petersen.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.MQTT.Broker.Authentication

Description

 

Synopsis

Documentation

class Exception (AuthenticationException a) => Authenticator a where Source #

A peer identity optionally associated with connection/session specific information. newtype Principal = Principal T.Text deriving (Eq, Ord, Show)

An Authenticator is able to determine a Principal's identity from a Request.

Minimal complete definition

newAuthenticator, authenticate, getPrincipal

Associated Types

data AuthenticatorConfig a Source #

data AuthenticationException a Source #

This Exception may be thrown by any operation within this class. Operations must only throw this type of exception. Other exceptions won't be catched and may kill the broker.

Methods

newAuthenticator :: AuthenticatorConfig a -> IO a Source #

Create a new authenticator instance from configuration.

authenticate :: a -> ConnectionRequest -> IO (Maybe PrincipalIdentifier) Source #

Try to determine a Principal's identity from a connection Request.

The operation shall return Nothing in case the authentication mechanism is working, but couldn't associate an identity. It shall throw an AuthenticationException in case of other problems.

getPrincipal :: a -> PrincipalIdentifier -> IO (Maybe Principal) Source #

Gets a principal by principal primary key (UUID).

The operation shall return Nothing in case the principal is not / no longer available. It shall throw an AuthenticationException in case of other problems.

data Principal Source #

Instances

Eq Principal Source # 
Show Principal Source # 
Generic Principal Source # 

Associated Types

type Rep Principal :: * -> * #

Binary Principal Source # 
type Rep Principal Source # 
type Rep Principal = D1 (MetaData "Principal" "Network.MQTT.Broker.Authentication" "mqtt-0.1.1.0-6z0Hs5qv6meCmpWtAOex9N" False) (C1 (MetaCons "Principal" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "principalUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Username))) (S1 (MetaSel (Just Symbol "principalQuota") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quota))) ((:*:) (S1 (MetaSel (Just Symbol "principalPublishPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Trie ()))) ((:*:) (S1 (MetaSel (Just Symbol "principalSubscribePermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Trie ()))) (S1 (MetaSel (Just Symbol "principalRetainPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Trie ())))))))

data Quota Source #

Instances

Eq Quota Source # 

Methods

(==) :: Quota -> Quota -> Bool #

(/=) :: Quota -> Quota -> Bool #

Ord Quota Source # 

Methods

compare :: Quota -> Quota -> Ordering #

(<) :: Quota -> Quota -> Bool #

(<=) :: Quota -> Quota -> Bool #

(>) :: Quota -> Quota -> Bool #

(>=) :: Quota -> Quota -> Bool #

max :: Quota -> Quota -> Quota #

min :: Quota -> Quota -> Quota #

Show Quota Source # 

Methods

showsPrec :: Int -> Quota -> ShowS #

show :: Quota -> String #

showList :: [Quota] -> ShowS #

Generic Quota Source # 

Associated Types

type Rep Quota :: * -> * #

Methods

from :: Quota -> Rep Quota x #

to :: Rep Quota x -> Quota #

Binary Quota Source # 

Methods

put :: Quota -> Put #

get :: Get Quota #

putList :: [Quota] -> Put #

type Rep Quota Source # 
type Rep Quota = D1 (MetaData "Quota" "Network.MQTT.Broker.Authentication" "mqtt-0.1.1.0-6z0Hs5qv6meCmpWtAOex9N" False) (C1 (MetaCons "Quota" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "quotaMaxIdleSessionTTL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) ((:*:) (S1 (MetaSel (Just Symbol "quotaMaxPacketSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "quotaMaxPacketIdentifiers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))) ((:*:) (S1 (MetaSel (Just Symbol "quotaMaxQueueSizeQoS0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) ((:*:) (S1 (MetaSel (Just Symbol "quotaMaxQueueSizeQoS1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "quotaMaxQueueSizeQoS2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))))))

data ConnectionRequest Source #

This class defines how the information gathered from a connection request looks like. An Authenticator may use whatever information it finds suitable to authenticate the Principal.

Constructors

ConnectionRequest 

Fields