dmcc-1.0.0.0: AVAYA DMCC API bindings and WebSockets server for AVAYA

Safe HaskellNone
LanguageHaskell2010

DMCC.Agent

Description

Agents in a DMCC API session enable call control over devices.

Synopsis

Documentation

data AgentEvent Source #

Events/errors are published to external clients of the agents and may be used by agent subscribers to provide information to user.

Constructors

TelephonyEvent

A telephony-related event, along with an updated snapshot.

StateChange

Arrives when an agent state change has been observed.

TelephonyEventError

An error caused by a telephony-related event.

Fields

RequestError

An error caused by a request from this agent.

Fields

data Agent Source #

An agent controlled by a DMCC API session.

Constructors

Agent 

Fields

Instances

data AgentError Source #

Exceptions thrown by agent-related routines and threads.

Instances

Data AgentError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AgentError -> c AgentError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AgentError #

toConstr :: AgentError -> Constr #

dataTypeOf :: AgentError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AgentError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AgentError) #

gmapT :: (forall b. Data b => b -> b) -> AgentError -> AgentError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AgentError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AgentError -> r #

gmapQ :: (forall d. Data d => d -> u) -> AgentError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AgentError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AgentError -> m AgentError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AgentError -> m AgentError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AgentError -> m AgentError #

Show AgentError Source # 
Exception AgentError Source # 

agentAction :: (MonadLoggerIO m, MonadCatch m) => Action -> AgentHandle -> m () Source #

Command an agent to do something.

Due to lack of global locking of the agents map an agent may be gone (released) by the time an action arrives to its actionChan. This is by design to avoid congestion during action processing.

controlAgent :: (MonadUnliftIO m, MonadLoggerIO m, MonadBaseControl IO m, MonadMask m) => SwitchName -> Extension -> Session -> m (Either AgentError AgentHandle) Source #

Enable an active agent to be monitored and controlled through DMCC API. If the agent has already been registered, return the old entry (it's safe to call this function with the same arguments multiple times).

processAgentAction :: (MonadUnliftIO m, MonadLoggerIO m, MonadBaseControl IO m, MonadCatch m) => AgentId -> DeviceId -> TVar AgentSnapshot -> Session -> Action -> m () Source #

Translate agent actions into actual DMCC API requests.

TODO Allow agents to control only own calls.

processAgentEvent :: (MonadUnliftIO m, MonadBaseControl IO m, MonadLoggerIO m, MonadCatch m) => AgentId -> DeviceId -> TVar AgentSnapshot -> TChan AgentEvent -> Session -> Response -> m () Source #

Process DMCC API events/errors for this agent to change its snapshot and broadcast events further.

sendWH :: (MonadUnliftIO m, MonadLoggerIO m, MonadCatch m) => (Request, Manager) -> AgentId -> AgentEvent -> m () Source #

Send agent event data to a web hook endpoint, ignoring possible exceptions.

releaseAgent :: (MonadUnliftIO m, MonadLoggerIO m, MonadBaseControl IO m, MonadCatch m) => AgentHandle -> m () Source #

Forget about an agent, releasing his device and monitors.

handleEvents :: (MonadLoggerIO m, MonadThrow m) => AgentHandle -> (AgentEvent -> m ()) -> m ThreadId Source #

Attach an event handler to an agent. Exceptions are not handled.