diameter
Main API of the diameter application.
This module provides the interface with which a user can implement a Diameter node that sends and receives messages using the Diameter protocol as defined in RFC 6733.
Basic usage consists of creating a representation of a locally implemented Diameter node and its capabilities with start_service/2, adding transport capability using add_transport/2 and sending Diameter requests and receiving Diameter answers with call/4. Incoming Diameter requests are communicated as callbacks to a diameter_app(3) callback modules as specified in the service configuration.
Beware the difference between diameter (not capitalized) and Diameter (capitalized). The former refers to the Erlang application named diameter whose main api is defined here, the latter to Diameter protocol in the sense of RFC 6733.
The diameter application must be started before calling most functions in this module.
DATA TYPES
Address()
DiameterIdentity()
Grouped()
OctetString()
Time()
Unsigned32()
UTF8String()
Types corresponding to RFC 6733 AVP Data Formats. Defined in diameter_dict(4).
application_alias() = term()
A name identifying a Diameter application in service configuration. Passed to call/4 when sending requests defined by the application.
application_module() = Mod
| [Mod | ExtraArgs]
| #diameter_callback{}
Mod = atom() ExtraArgs = list()
A module implementing the callback interface defined in diameter_app(3), along with any extra arguments to be appended to those documented for the interface. Note that extra arguments specific to an outgoing request can be specified to call/4, in which case those are are appended to any module-specific extra arguments.
Specifying a #diameter_callback{}
record allows individual
functions to be configured in place of the usual diameter_app(3) callbacks.
See that module for details.
application_opt()
Options defining a Diameter application. Has one the following types.
{alias, application_alias()}
An unique identifier for the application in the scope of the
service.
Defaults to the value of the dictionary
option if
unspecified.
{dictionary, atom()}
The name of an encode/decode module for the Diameter messages defined by the application. These modules are generated from a specification file whose format is documented in diameter_dict(4).
{module, application_module()}
The callback module with which messages of the Diameter application are handled. See diameter_app(3) for the required interface and semantics.
{state, term()}
The initial callback state.
The prevailing state is passed to some
diameter_app(3)
callbacks, which can then return a new state.
Defaults to the value of the alias
option if unspecified.
{call_mutates_state, true|false}
Specifies whether or not the pick_peer/4
application callback can modify the application state.
Defaults to false
if unspecified.
Note!
pick_peer/4 callbacks are serialized when these are allowed to modify state, which is a potential performance bottleneck. A simple Diameter client may suffer no ill effects from using mutable state but a server or agent that responds to incoming request should probably avoid it.
{answer_errors, callback|report|discard}
Determines the manner in which incoming answer messages containing decode errors are handled.
If callback
then errors result in a handle_answer/4
callback in the same fashion as for handle_request/3, with
errors communicated in the errors
field of the
#diameter_packet{}
passed to the callback.
If report
then an answer containing errors is discarded
without a callback and a warning report is written to the log.
If discard
then an answer containing errors is silently
discarded without a callback.
In both the report
and discard
cases the return value
for the call/4 invocation in
question is as if a callback had taken place and returned
{error, failure}
.
Defaults to report
if unspecified.
{request_errors, answer_3xxx|answer|callback}
Determines the manner in which incoming requests are handled when an error other than 3007, DIAMETER_APPLICATION_UNSUPPORTED (which cannot be associated with an application callback module), is detected.
If answer_3xxx
then requests are answered without a
handle_request/3 callback taking place.
If answer
then even 5xxx errors are answered without a
callback unless the connection in question has configured the RFC 3588
common dictionary as noted below.
If callback
then a handle_request/3 callback always takes
place and the return value determines the answer sent to the peer.
Defaults to answer_3xxx
if unspecified.
Note!
Answers sent by diameter set the E-bit in the Diameter Header.
Since RFC 3588 allowed only 3xxx result codes in an
answer-message
, answer
has the same semantics as
answer_3xxx
if the peer connection in question has configured
the RFC 3588 common dictionary, diameter_gen_base_rfc3588
.
RFC 6733 allows both 3xxx and 5xxx result codes in an
answer-message
so a connection configured with the RFC 6733
common dictionary, diameter_gen_base_rfc6733
, does
distinguish between answer_3xxx
and answer
.
call_opt()
Options available to call/4 when sending an outgoing Diameter request. Has one of the following types.
{extra, list()}
Extra arguments to append to callbacks to the callback module in question. These are appended to any extra arguments configured on the callback itself. Multiple options append to the argument list.
{filter, peer_filter()}
A filter to apply to the list of available peers before passing them to
the pick_peer/4
callback for the application in question.
Multiple options are equivalent a single all
filter on the
corresponding list of filters.
Defaults to none
.
{timeout, Unsigned32()}
The number of milliseconds after which the request should timeout. Defaults to 5000.
detach
Causes call/4 to return ok
as
soon as the request in
question has been encoded instead of waiting for and returning
the result from a subsequent handle_answer/4 or
handle_error/4 callback.
An invalid option will cause call/4 to fail.
capability()
AVP values sent in outgoing CER or CEA messages during capabilities exchange. Can be configured both on a service and a transport, values specified on the latter taking precedence over any specified on the former. Has one of the following types.
{'Origin-Host', DiameterIdentity()}
{'Origin-Realm', DiameterIdentity()}
{'Host-IP-Address', [Address()]}
An address list is available to the start function of a transport module, which can return a new list for use in the subsequent CER or CEA. Host-IP-Address need not be specified if the transport module in question communicates an address list as described in diameter_transport(3)
{'Vendor-Id', Unsigned32()}
{'Product-Name', UTF8String()}
{'Origin-State-Id', Unsigned32()}
Origin-State-Id is optional but will be included in outgoing messages
sent by diameter itself: CER/CEA, DWR/DWA and DPR/DPA.
Setting a value of 0
(zero) is equivalent to not setting a
value as documented in RFC 6733.
The function origin_state_id/0
can be used as to retrieve a value that is computed when the diameter
application is started.
{'Supported-Vendor-Id', [Unsigned32()]}
{'Auth-Application-Id', [Unsigned32()]}
{'Inband-Security-Id', [Unsigned32()]}
Inband-Security-Id defaults to the empty list, which is equivalent to a list containing only 0 (= NO_INBAND_SECURITY). If 1 (= TLS) is specified then TLS is selected if the CER/CEA received from the peer offers it.
{'Acct-Application-Id', [Unsigned32()]}
{'Vendor-Specific-Application-Id', [Grouped()]}
{'Firmware-Revision', Unsigned32()}
Note that each tuple communicates one or more AVP values. It is an error to specify duplicate tuples.
evaluable() = {M,F,A} | fun() | [evaluable() | A]
An expression that can be evaluated as a function in the following sense.
eval([{M,F,A} | T]) -> apply(M, F, T ++ A); eval([[F|A] | T]) -> eval([F | T ++ A]); eval([F|A]) -> apply(F, A); eval(F) -> eval([F]).
Applying an evaluable()
E
to an argument list A
is meant in the sense of eval([E|A])
.
Warning!
Beware of using fun expressions of the form fun Name/Arity
in
situations in which the fun is not short-lived
and code is to be upgraded at runtime since any processes retaining
such a fun will have a reference to old code.
In particular, such a value is typically inappropriate in
configuration passed to start_service/2 or add_transport/2.
peer_filter() = term()
A filter passed to call/4 in order to select candidate peers for a pick_peer/4 callback. Has one of the following types.
none
Matches any peer. This is a convenience that provides a filter equivalent to no filter at all.
host
Matches only those peers whose Origin-Host
has the same value
as Destination-Host
in the outgoing request in question,
or any peer if the request does not contain
a Destination-Host
AVP.
realm
Matches only those peers whose Origin-Realm
has the same value
as Destination-Realm
in the outgoing request in question,
or any peer if the request does not contain
a Destination-Realm
AVP.
{host, any|DiameterIdentity()}
Matches only those peers whose Origin-Host
has the
specified value, or all peers if the atom any
.
{realm, any|DiameterIdentity()
Matches only those peers whose Origin-Realm
has the
specified value, or all peers if the atom any
.
{eval, evaluable()}
Matches only those peers for which the specified
evaluable()
returns
true
on the connection's diameter_caps
record.
Any other return value or exception is equivalent to false
.
{neg, peer_filter()}
Matches only those peers not matched by the specified filter.
{all, [peer_filter()]}
Matches only those peers matched by each filter in the specified list.
{any, [peer_filter()]}
Matches only those peers matched by at least one filter in the specified list.
An invalid filter is equivalent to {any,[]}
, a filter
that matches no peer.
Note!
The host
and realm
filters examine the
outgoing request as passed to call/4,
assuming that this is a record- or list-valued diameter_codec:message()
,
and that the message contains at most one of each AVP.
If this is not the case then the {host|realm, DiameterIdentity()}
filters must be used to achieve the desired result.
An empty DiameterIdentity()
(which should not be typical)
matches all hosts/realms for the purposes of filtering.
Warning!
A host
filter is not typically desirable when setting
Destination-Host since it will remove peer agents from the
candidates list.
service_event() = #diameter_event{service = service_name(),
info = service_event_info()}
An event message sent to processes that have subscribed to these using subscribe/1.
service_event_info() = term()
The info
field of a service_event() record.
Can have one of the following types.
start
stop
The service is being started or stopped.
No event precedes a start
event.
No event follows a stop
event and this event
implies the termination of all transport processes.
{up, Ref, Peer, Config, Pkt}
{up, Ref, Peer, Config}
{down, Ref, Peer, Config}
Ref = transport_ref() Peer = diameter_app:peer() Config = {connect|listen, [transport_opt()]} Pkt = #diameter_packet{}
The RFC 3539 watchdog state machine has
transitioned into (up
) or out of (down
) the OKAY
state.
If a #diameter_packet{}
is present in an up
event
then there has been a capabilties exchange on a newly established
transport connection and the record contains the received CER or CEA.
Otherwise a connection has reestablished without the loss or
connectivity.
Note that a single up
or down
event for a given peer
corresponds to multiple peer_up/3 or peer_up/3
callbacks, one for each of the Diameter applications negotiated during
capablilities exchange.
That is, the event communicates connectivity with the
peer as a whole while the callbacks communicate connectivity with
respect to individual Diameter applications.
{reconnect, Ref, Opts}
Ref = transport_ref() Opts = [transport_opt()]
A connecting transport is attempting to establish/reestablish a transport connection with a peer following reconnect_timer or watchdog_timer expiry.
{closed, Ref, Reason, Config}
Ref = transport_ref() Config = {connect|listen, [transport_opt()]}
Capabilities exchange has failed.
Reason
can have one of the following types.
{'CER', Result, Caps, Pkt}
Result = ResultCode | {capabilities_cb, CB, ResultCode|discard} Caps = #diameter_caps{} Pkt = #diameter_packet{} ResultCode = integer() CB = evaluable()
An incoming CER has been answered with the indicated result code or
discarded.
Caps
contains pairs of values for the local node and remote
peer.
Pkt
contains the CER in question.
In the case of rejection by a capabilities callback, the tuple
contains the rejecting callback.
{'CER', Caps, {ResultCode, Pkt}}
ResultCode = integer() Caps = #diameter_caps{} Pkt = #diameter_packet{}
An incoming CER contained errors and has been answered with the
indicated result code.
Caps
contains only values for the local node.
Pkt
contains the CER in question.
{'CER', timeout}
An expected CER was not received within capx_timeout of connection establishment.
{'CEA', Result, Caps, Pkt}
Result = integer() | atom() | {capabilities_cb, CB, ResultCode|discard} Caps = #diameter_caps{} Pkt = #diameter_packet{} ResultCode = integer()
An incoming CEA has been rejected for the indicated reason.
An integer-valued Result
indicates the result code sent
by the peer.
Caps
contains pairs of values for the local node and remote
peer.
Pkt
contains the CEA in question.
In the case of rejection by a capabilities callback, the tuple
contains the rejecting callback.
{'CEA', Caps, Pkt}
Caps = #diameter_caps{} Pkt = #diameter_packet{}
An incoming CEA contained errors and has been rejected.
Caps
contains only values for the local node.
Pkt
contains the CEA in question.
{'CEA', timeout}
An expected CEA was not received within capx_timeout of connection establishment.
{watchdog, Ref, PeerRef, {From, To}, Config}
Ref = transport_ref() PeerRef = diameter_app:peer_ref() From, To = initial | okay | suspect | down | reopen Config = {connect|listen, [transport_opt()]}
An RFC 3539 watchdog state machine has changed state.
any()
For forward compatibility, a subscriber should be prepared to receive info fields of forms other than the above.
service_name() = term()
The name of a service as passed to start_service/2 and with which the service is identified. There can be at most one service with a given name on a given node. Note that erlang:make_ref/0 can be used to generate a service name that is somewhat unique.
service_opt()
An option passed to start_service/2.
Can be any capability()
as well as the following.
{application, [application_opt()]}
Defines a Diameter application supported by the service.
A service must configure one tuple for each Diameter
application it intends to support.
For an outgoing Diameter request, the relevant application_alias()
is
passed to call/4, while for an
incoming request the application identifier in the message
header determines the application, the identifier being specified in
the application's dictionary file.
Warning!
The capabilities advertised by a node must match its configured
applications. In particular, application
configuration must
be matched by corresponding capability() configuration, of
Application-Id AVP's in particular.
{restrict_connections, false
| node
| nodes
| [node()]
| evaluable()}
Specifies the degree to which the service allows multiple transport connections to the same peer.
If type [node()]
then a connection is rejected if another already
exists on any of the specified nodes.
Types false
, node
, nodes
and
evaluable() are equivalent to
[]
, [node()]
, [node()|nodes()]
and the
evaluated value respectively, evaluation of each expression taking
place whenever a new connection is to be established.
Note that false
allows an unlimited number of connections to be
established with the same peer.
Multiple connections are independent and governed by their own peer and watchdog state machines.
Defaults to nodes
.
{sequence, {H,N} | evaluable()}
Specifies a constant value H
for the topmost 32-N
bits of
of 32-bit End-to-End and Hop-by-Hop identifiers generated
by the service, either explicity or as a return value of a function
to be evaluated at start_service/2.
In particular, an identifier Id
is mapped to a new identifier
as follows.
(H bsl N) bor (Id band ((1 bsl N) - 1))
Note that RFC 6733 requires that End-to-End identifiers remain unique
for a period of at least 4 minutes and that this and the call rate
places a lower bound on the appropriate values of N
:
at a rate of R
requests per second an N
-bit counter
traverses all of its values in (1 bsl N) div (R*60)
minutes so
the bound is 4*R*60 =< 1 bsl N
.
N
must lie in the range 0..32
and H
must be a
non-negative integer less than 1 bsl (32-N)
.
Defaults to {0,32}
.
Warning!
Multiple Erlang nodes implementing the same Diameter node should be configured with different sequence masks to ensure that each node uses a unique range of End-to-End and Hop-by-Hop identifiers for outgoing requests.
{share_peers, boolean() | [node()] | evaluable()}
Specifies nodes to which peer connections established on the local
Erlang node are communicated.
Shared peers become available in the remote candidates list passed to
pick_peer/4 callbacks on remote nodes whose services are
configured to use them: see use_shared_peers
below.
If false
then peers are not shared.
If [node()]
then peers are shared with the specified list of
nodes.
If evaluable()
then peers are shared with the nodes returned
by the specified function, evaluated whenever a peer connection
becomes available or a remote service requests information about local
connections.
The value true
is equivalent to fun erlang:nodes/0
.
The value node()
in a node list is ignored, so a collection of
services can all be configured to share with the same list of
nodes.
Defaults to false
.
Note!
Peers are only shared with services of the same name for the purpose
of sending outgoing requests.
Since the value of the application_opt() alias
, passed to
call/4, is the handle for identifying a peer as a suitable
candidate, services that share peers must use the same aliases to
identify their supported applications.
They should typically also configure identical capabilities(), since
by sharing peer connections they are distributing the implementation
of a single Diameter node across multiple Erlang nodes.
{spawn_opt, [term()]}
An options list passed to erlang:spawn_opt/2 when spawning a process for an
incoming Diameter request, unless the transport in question
specifies another value.
Options monitor
and link
are ignored.
Defaults to the empty list.
{use_shared_peers, boolean() | [node()] | evaluable()}
Specifies nodes from which communicated peers are made available in the remote candidates list of pick_peer/4 callbacks.
If false
then remote peers are not used.
If [node()]
then only peers from the specified list of nodes
are used.
If evaluable()
then only peers returned by the specified
function are used, evaluated whenever a remote service communicates
information about an available peer connection.
The value true
is equivalent to fun erlang:nodes/0
.
The value node()
in a node list is ignored.
Defaults to false
.
Note!
A service that does not use shared peers will always pass the empty list as the second argument of pick_peer/4 callbacks.
Warning!
Sending a request over a peer connection on a remote node is less
efficient than sending it over a local connection.
It may be preferable to make use of the service_opt()
restrict_connections
and maintain a dedicated connection on
each node from which requests are sent.
transport_opt()
An option passed to add_transport/2. Has one of the following types.
{applications, [application_alias()]}
The list of Diameter applications to which the transport should be restricted. Defaults to all applications configured on the service in question. Applications not configured on the service in question are ignored.
Warning!
The capabilities advertised by a node must match its configured
applications.
In particular, setting applications
on a transport typically
implies having to set matching Application-Id AVP's in a
capabilities() tuple.
{capabilities, [capability()]}
AVP's used to construct outgoing CER/CEA messages. Values take precedence over any specified on the service in question.
Specifying a capability as a transport option may be particularly appropriate for Inband-Security-Id, in case TLS is desired over TCP as implemented by diameter_tcp(3).
{capabilities_cb, evaluable()}
A callback invoked upon reception of CER/CEA during capabilities
exchange in order to ask whether or not the connection should
be accepted.
Applied to the transport_ref()
and
#diameter_caps{}
record of the connection.
The return value can have one of the following types.
ok
Accept the connection.
integer()
Causes an incoming CER to be answered with the specified Result-Code.
discard
Causes an incoming CER to be discarded without CEA being sent.
unknown
Equivalent to returning 3010
, DIAMETER_UNKNOWN_PEER.
Returning anything but ok
or a 2xxx series result
code causes the transport connection to be broken.
Multiple capabilities_cb
options can be specified, in which
case the corresponding callbacks are applied until either all return
ok
or one does not.
{capx_timeout, Unsigned32()}
The number of milliseconds after which a transport process having an established transport connection will be terminated if the expected capabilities exchange message (CER or CEA) is not received from the peer. For a connecting transport, the timing of reconnection attempts is governed by watchdog_timer or reconnect_timer expiry. For a listening transport, the peer determines the timing.
Defaults to 10000.
{disconnect_cb, evaluable()}
A callback invoked prior to terminating the transport process of a
transport connection having watchdog state OKAY
.
Applied to Reason=transport|service|application
and the
transport_ref()
and
diameter_app:peer()
in question, Reason
indicating whether the diameter
application is being stopped, the service in question is being stopped
at stop_service/1 or
the transport in question is being removed at remove_transport/2,
respectively.
The return value can have one of the following types.
{dpr, [option()]}
Causes Disconnect-Peer-Request to be sent to the peer, the transport
process being terminated following reception of
Disconnect-Peer-Answer or timeout.
An option()
can be one of the following.
{cause, 0|rebooting|1|busy|2|goaway}
The Disconnect-Cause to send, REBOOTING
, BUSY
and
DO_NOT_WANT_TO_TALK_TO_YOU
respectively.
Defaults to rebooting
for Reason=service|application
and
goaway
for Reason=transport
.
{timeout, Unsigned32()}
The number of milliseconds after which the transport process is terminated if DPA has not been received. Defaults to 1000.
dpr
Equivalent to {dpr, []}
.
close
Causes the transport process to be terminated without Disconnect-Peer-Request being sent to the peer.
ignore
Equivalent to not having configured the callback.
Multiple disconnect_cb
options can be specified, in which
case the corresponding callbacks are applied until one of them returns
a value other than ignore
.
All callbacks returning ignore
is equivalent to not having
configured them.
Defaults to a single callback returning dpr
.
{length_errors, exit|handle|discard}
Specifies how to deal with errors in the Message Length field of the Diameter Header in an incoming message. An error in this context is that the length is not at least 20 bytes (the length of a Header), is not a multiple of 4 (a valid length) or is not the length of the message in question, as received over the transport interface documented in diameter_transport(3).
If exit
then a warning report is emitted and the parent of the
transport process in question exits, which causes the transport
process itself to exit as described in diameter_transport(3).
If handle
then the message is processed as usual, a resulting
handle_request/3 or handle_answer/4 callback (if one takes
place) indicating the 5015
error (DIAMETER_INVALID_MESSAGE_LENGTH).
If discard
then the message in question is silently discarded.
Defaults to exit
.
Note!
The default value reflects the fact that a transport module for a stream-oriented transport like TCP may not be able to recover from a message length error since such a transport must use the Message Length header to divide the incoming byte stream into individual Diameter messages. An invalid length leaves it with no reliable way to rediscover message boundaries, which may result in the failure of subsequent messages. See diameter_tcp(3) for the behaviour of that module.
{reconnect_timer, Tc}
Tc = Unsigned32()
For a connecting transport, the RFC 6733 Tc timer, in milliseconds. Note that this timer determines the frequency with which a transport will attempt to establish a connection with its peer only before an initial connection is established: once there is an initial connection it's watchdog_timer that determines the frequency of reconnection attempts, as required by RFC 3539.
For a listening transport, the timer specifies the time after which a previously connected peer will be forgotten: a connection after this time is regarded as an initial connection rather than a reestablishment, causing the RFC 3539 state machine to pass to state OKAY rather than REOPEN. Note that these semantics are not governed by the RFC and that a listening transport's reconnect_timer should be greater than its peer's Tw plus jitter.
Defaults to 30000 for a connecting transport and 60000 for a listening transport.
{spawn_opt, [term()]}
An options list passed to erlang:spawn_opt/2 when spawning a process for an
incoming Diameter request.
Options monitor
and link
are ignored.
Defaults to the list configured on the service if not specified.
{transport_config, term()}
{transport_config, term(), Unsigned32() | infinity}
A term passed as the third argument to the start/3 function of the relevant transport module in order to start a transport process. Defaults to the empty list if unspecified.
The 3-tuple form additionally specifies an interval, in milliseconds, after which a started transport process should be terminated if it has not yet established a connection. For example, the following options on a connecting transport request a connection with one peer over SCTP or another (typically the same) over TCP.
{transport_module, diameter_sctp} {transport_config, SctpOpts, 5000} {transport_module, diameter_tcp} {transport_config, TcpOpts}
To listen on both SCTP and TCP, define one transport for each.
{transport_module, atom()}
A module implementing a transport process as defined in diameter_transport(3).
Defaults to diameter_tcp
if unspecified.
Multiple transport_module
and transport_config
options are allowed.
The order of these is significant in this case (and only in this case),
a transport_module
being paired with the first
transport_config
following it in the options list, or the default value for trailing
modules.
Transport starts will be attempted with each of the
modules in order until one establishes a connection within the
corresponding timeout (see below) or all fail.
{watchdog_config, [{okay|suspect, non_neg_integer()}]}
Specifies configuration that alters the behaviour of the watchdog
state machine.
On key okay
, the non-negative number of answered DWR
messages before transitioning from REOPEN to OKAY.
On key suspect
, the number of watchdog timeouts before
transitioning from OKAY to SUSPECT when DWR is unanswered, or 0 to
not make the transition.
Defaults to [{okay, 3}, {suspect, 1}]
.
Not specifying a key is equivalent to specifying
the default value for that key.
Warning!
The default value is as required by RFC 3539: changing it results in non-standard behaviour that should only be used to simulate misbehaving nodes during test.
{watchdog_timer, TwInit}
TwInit = Unsigned32() | {M,F,A}
The RFC 3539 watchdog timer. An integer value is interpreted as the RFC's TwInit in milliseconds, a jitter of ± 2 seconds being added at each rearming of the timer to compute the RFC's Tw. An MFA is expected to return the RFC's Tw directly, with jitter applied, allowing the jitter calculation to be performed by the callback.
An integer value must be at least 6000 as required by RFC 3539. Defaults to 30000 if unspecified.
Unrecognized options are silently ignored but are returned unmodified by service_info/2 and can be referred to in predicate functions passed to remove_transport/2.
transport_ref() = reference()
An reference returned by add_transport/2 that identifies the configuration.
Functions
add_transport(SvcName, {connect|listen, [Opt]}) -> {ok, Ref} | {error, Reason}
SvcName = service_name()
Opt = transport_opt()
Ref = transport_ref()
Reason = term()
Add transport capability to a service.
The service will start transport processes as required in order to
establish a connection with the peer, either by connecting to the peer
(connect
) or by accepting incoming connection requests
(listen
).
A connecting transport establishes transport connections with at most
one peer, an listening transport potentially with many.
The diameter application takes responsibility for exchanging CER/CEA with the peer. Upon successful completion of capabilities exchange the service calls each relevant application module's peer_up/3 callback after which the caller can exchange Diameter messages with the peer over the transport. In addition to CER/CEA, the service takes responsibility for the handling of DWR/DWA and required by RFC 3539, as well as for DPR/DPA.
The returned reference uniquely identifies the transport within the scope of the service. Note that the function returns before a transport connection has been established.
Note!
It is not an error to add a transport to a service that has not yet been configured: a service can be started after configuring its transports.
call(SvcName, App, Request, [Opt]) -> Answer | ok | {error, Reason}
SvcName = service_name()
App = application_alias()
Request = diameter_codec:message()
Answer = term()
Opt = call_opt()
Send a Diameter request message.
App
specifies the Diameter application in which the request is
defined and callbacks to the corresponding callback module
will follow as described below and in diameter_app(3).
Unless the detach
option is specified, the call returns either
when an answer message is received from the peer or an error occurs.
In the answer case, the return value is as returned by a
handle_answer/4 callback.
In the error case, whether or not the error is returned directly
by diameter or from a handle_error/4
callback depends on whether or not the outgoing request is
successfully encoded for transmission to the peer, the cases being
documented below.
If there are no suitable peers, or if
pick_peer/4
rejects them by returning false
, then {error,no_connection}
is returned.
Otherwise pick_peer/4 is followed by a
prepare_request/3 callback, the message is encoded and then sent.
There are several error cases which may prevent an answer from being received and passed to a handle_answer/4 callback:
-
If the initial encode of the outgoing request fails, then the request process fails and
{error,encode}
is returned. -
If the request is successfully encoded and sent but the answer times out then a handle_error/4 callback takes place with
Reason = timeout
. -
If the request is successfully encoded and sent but the service in question is stopped before an answer is received then a handle_error/4 callback takes place with
Reason = cancel
. -
If the transport connection with the peer goes down after the request has been sent but before an answer has been received then an attempt is made to resend the request to an alternate peer. If no such peer is available, or if the subsequent pick_peer/4 callback rejects the candidates, then a handle_error/4 callback takes place with
Reason = failover
. If a peer is selected then a prepare_retransmit/3 callback takes place, after which the semantics are the same as following an initial prepare_request/3 callback. -
If an encode error takes place during retransmission then the request process fails and
{error,failure}
is returned. -
If an application callback made in processing the request fails (pick_peer, prepare_request, prepare_retransmit, handle_answer or handle_error) then either
{error,encode}
or{error,failure}
is returned depending on whether or not there has been an attempt to send the request over the transport.
Note that {error,encode}
is the only return value which
guarantees that the request has not been sent over the
transport connection.
origin_state_id() -> Unsigned32()
Return a reasonable value for use as Origin-State-Id in outgoing messages.
The value returned is the number of seconds since 19680120T031408Z,
the first value that can be encoded as a Diameter Time()
,
at the time the diameter application was started.
remove_transport(SvcName, Pred) -> ok | {error, Reason}
SvcName = service_name()
Pred = Fun | MFA | transport_ref() | list() | true | false
Fun = fun((transport_ref(), connect|listen, list()) -> boolean())
| fun((transport_ref(), list()) -> boolean())
| fun((list()) -> boolean())
MFA = {atom(), atom(), list()}
Reason = term()
Remove previously added transports.
Pred
determines which transports to remove.
An arity-3-valued Pred
removes all transports for which
Pred(Ref, Type, Opts)
returns true
, where Type
and
Opts
are as passed to add_transport/2 and Ref
is
as returned by it.
The remaining forms are equivalent to an arity-3 fun as follows.
Pred = fun(transport_ref(), list()): fun(Ref, _, Opts) -> Pred(Ref, Opts) end Pred = fun(list()): fun(_, _, Opts) -> Pred(Opts) end Pred = transport_ref(): fun(Ref, _, _) -> Pred == Ref end Pred = list(): fun(_, _, Opts) -> [] == Pred -- Opts end Pred = true: fun(_, _, _) -> true end Pred = false: fun(_, _, _) -> false end Pred = {M,F,A}: fun(Ref, Type, Opts) -> apply(M, F, [Ref, Type, Opts | A]) end
Removing a transport causes the corresponding transport processes to be terminated. Whether or not a DPR message is sent to a peer is controlled by value of disconnect_cb configured on the transport.
service_info(SvcName, Info) -> term()
SvcName = service_name()
Info = Item | [Info]
Item = atom()
Return information about a started service.
Requesting info for an unknown service causes undefined
to be
returned.
Requesting a list of items causes a tagged list to be
returned.
Item
can be one of the following.
'Origin-Host'
'Origin-Realm'
'Vendor-Id'
'Product-Name'
'Origin-State-Id'
'Host-IP-Address'
'Supported-Vendor'
'Auth-Application-Id'
'Inband-Security-Id'
'Acct-Application-Id'
'Vendor-Specific-Application-Id'
'Firmware-Revision'
Return a capability value as configured with start_service/2.
applications
Return the list of applications as configured with start_service/2.
capabilities
Return a tagged list of all capabilities values as configured with start_service/2.
transport
Return a list containing one entry for each of the service's transport as configured with add_transport/2. Each entry is a tagged list containing both configuration and information about established peer connections. An example return value with for a client service with Origin-Host "client.example.com" configured with a single transport connected to "server.example.com" might look as follows.
[[{ref,#Ref<0.0.0.93>}, {type,connect}, {options,[{transport_module,diameter_tcp}, {transport_config,[{ip,{127,0,0,1}}, {raddr,{127,0,0,1}}, {rport,3868}, {reuseaddr,true}]}]}, {watchdog,{<0.66.0>,{1346,171491,996448},okay}}, {peer,{<0.67.0>,{1346,171491,999906}}}, {apps,[{0,common}]}, {caps,[{origin_host,{"client.example.com","server.example.com"}}, {origin_realm,{"example.com","example.com"}}, {host_ip_address,{[{127,0,0,1}],[{127,0,0,1}]}}, {vendor_id,{0,193}}, {product_name,{"Client","Server"}}, {origin_state_id,{[],[]}}, {supported_vendor_id,{[],[]}}, {auth_application_id,{[0],[0]}}, {inband_security_id,{[],[0]}}, {acct_application_id,{[],[]}}, {vendor_specific_application_id,{[],[]}}, {firmware_revision,{[],[]}}, {avp,{[],[]}}]}, {port,[{owner,<0.69.0>}, {module,diameter_tcp}, {socket,{{127,0,0,1},48758}}, {peer,{{127,0,0,1},3868}}, {statistics,[{recv_oct,656}, {recv_cnt,6}, {recv_max,148}, {recv_avg,109}, {recv_dvi,19}, {send_oct,836}, {send_cnt,6}, {send_max,184}, {send_avg,139}, {send_pend,0}]}]}, {statistics,[{{{0,258,0},recv},3}, {{{0,258,1},send},3}, {{{0,257,0},recv},1}, {{{0,257,1},send},1}, {{{0,258,0},recv,{'Result-Code',2001}},3}, {{{0,280,1},recv},2}, {{{0,280,0},send},2}]}]]
Here ref
is a transport_ref()
and options
the corresponding transport_opt()
list passed to
add_transport/2.
The watchdog
entry shows the state of a connection's RFC 3539 watchdog
state machine.
The peer
entry identifies the diameter_app:peer_ref()
for
which there will have been peer_up/3 callbacks for the
Diameter applications identified by the apps
entry,
common
being the application_alias()
.
The caps
entry identifies the capabilities sent by the local
node and received from the peer during capabilities exchange.
The port
entry displays socket-level information about the
transport connection.
The statistics
entry presents Diameter-level counters,
an entry like {{{0,280,1},recv},2}
saying that the client has
received 2 DWR messages: {0,280,1} = {Application_Id, Command_Code,
R_Flag}
.
Note that watchdog
, peer
, apps
, caps
and port
entries depend on connectivity
with the peer and may not be present.
Note also that the statistics
entry presents values acuumulated
during the lifetime of the transport configuration.
A listening transport presents its information slightly differently
since there may be multiple accepted connections for the same
transport_ref()
.
The transport
info returned by a server with a single client
connection might look as follows.
[[{ref,#Ref<0.0.0.61>}, {type,listen}, {options,[{transport_module,diameter_tcp}, {transport_config,[{reuseaddr,true}, {ip,{127,0,0,1}}, {port,3868}]}]}, {accept,[[{watchdog,{<0.56.0>,{1346,171481,226895},okay}}, {peer,{<0.58.0>,{1346,171491,999511}}}, {apps,[{0,common}]}, {caps,[{origin_host,{"server.example.com","client.example.com"}}, {origin_realm,{"example.com","example.com"}}, {host_ip_address,{[{127,0,0,1}],[{127,0,0,1}]}}, {vendor_id,{193,0}}, {product_name,{"Server","Client"}}, {origin_state_id,{[],[]}}, {supported_vendor_id,{[],[]}}, {auth_application_id,{[0],[0]}}, {inband_security_id,{[],[]}}, {acct_application_id,{[],[]}}, {vendor_specific_application_id,{[],[]}}, {firmware_revision,{[],[]}}, {avp,{[],[]}}]}, {port,[{owner,<0.62.0>}, {module,diameter_tcp}, {socket,{{127,0,0,1},3868}}, {peer,{{127,0,0,1},48758}}, {statistics,[{recv_oct,1576}, {recv_cnt,16}, {recv_max,184}, {recv_avg,98}, {recv_dvi,26}, {send_oct,1396}, {send_cnt,16}, {send_max,148}, {send_avg,87}, {send_pend,0}]}]}], [{watchdog,{<0.72.0>,{1346,171491,998404},initial}}]]}, {statistics,[{{{0,280,0},recv},7}, {{{0,280,1},send},7}, {{{0,258,0},send,{'Result-Code',2001}},3}, {{{0,258,1},recv},3}, {{{0,258,0},send},3}, {{{0,280,1},recv},5}, {{{0,280,0},send},5}, {{{0,257,1},recv},1}, {{{0,257,0},send},1}]}]]
The information presented here is as in the connect
case except
that the client connections are grouped under an accept
tuple.
connections
Return a list containing one entry for every established transport
connection whose watchdog state machine is not in the down
state.
This is a flat view of transport
info which lists only active
connections and for which Diameter-level statistics are accumulated
only for the lifetime of the transport connection.
A return value for the server above might look as follows.
[[{ref,#Ref<0.0.0.61>}, {type,accept}, {options,[{transport_module,diameter_tcp}, {transport_config,[{reuseaddr,true}, {ip,{127,0,0,1}}, {port,3868}]}]}, {watchdog,{<0.56.0>,{1346,171481,226895},okay}}, {peer,{<0.58.0>,{1346,171491,999511}}}, {apps,[{0,common}]}, {caps,[{origin_host,{"server.example.com","client.example.com"}}, {origin_realm,{"example.com","example.com"}}, {host_ip_address,{[{127,0,0,1}],[{127,0,0,1}]}}, {vendor_id,{193,0}}, {product_name,{"Server","Client"}}, {origin_state_id,{[],[]}}, {supported_vendor_id,{[],[]}}, {auth_application_id,{[0],[0]}}, {inband_security_id,{[],[]}}, {acct_application_id,{[],[]}}, {vendor_specific_application_id,{[],[]}}, {firmware_revision,{[],[]}}, {avp,{[],[]}}]}, {port,[{owner,<0.62.0>}, {module,diameter_tcp}, {socket,{{127,0,0,1},3868}}, {peer,{{127,0,0,1},48758}}, {statistics,[{recv_oct,10124}, {recv_cnt,132}, {recv_max,184}, {recv_avg,76}, {recv_dvi,9}, {send_oct,10016}, {send_cnt,132}, {send_max,148}, {send_avg,75}, {send_pend,0}]}]}, {statistics,[{{{0,280,0},recv},62}, {{{0,280,1},send},62}, {{{0,258,0},send,{'Result-Code',2001}},3}, {{{0,258,1},recv},3}, {{{0,258,0},send},3}, {{{0,280,1},recv},66}, {{{0,280,0},send},66}, {{{0,257,1},recv},1}, {{{0,257,0},send},1}]}]]
Note that there may be multiple entries with the same ref
, in
contrast to transport
info.
statistics
Return a {{Counter, Ref}, non_neg_integer()}
list of counter values.
Ref
can be either a transport_ref()
or a diameter_app:peer_ref()
.
Entries for the latter are folded into corresponding entries for the
former as peer connections go down.
Entries for both are removed at remove_transport/2.
The Diameter-level statistics returned by transport
and
connections
info are based upon these entries.
diameter_app:peer_ref()
Return transport configuration associated with a single peer, as
passed to add_transport/2.
The returned list is empty if the peer is unknown.
Otherwise it contains the ref
, type
and options
tuples as in transport
and connections
info above.
For example:
[{ref,#Ref<0.0.0.61>}, {type,accept}, {options,[{transport_module,diameter_tcp}, {transport_config,[{reuseaddr,true}, {ip,{127,0,0,1}}, {port,3868}]}]}]
session_id(Ident) -> OctetString()
Ident = DiameterIdentity()
Return a value for a Session-Id AVP.
The value has the form required by section 8.8 of RFC 6733. Ident should be the Origin-Host of the peer from which the message containing the returned value will be sent.
start() -> ok | {error, Reason}
Start the diameter application.
The diameter application must be started before starting a service.
In a production system this is typically accomplished by a boot
file, not by calling start/0
explicitly.
start_service(SvcName, Options) -> ok | {error, Reason}
SvcName = service_name()
Options = [service_opt()]
Reason = term()
Start a diameter service.
A service defines a locally-implemented Diameter node, specifying the capabilities to be advertised during capabilities exchange. Transports are added to a service using add_transport/2.
Note!
A transport can both override its service's capabilities and restrict its supported Diameter applications so "service = Diameter node as identified by Origin-Host" is not necessarily the case.
stop() -> ok | {error, Reason}
Stop the diameter application.
stop_service(SvcName) -> ok | {error, Reason}
SvcName = service_name()
Reason = term()
Stop a diameter service.
Stopping a service causes all associated transport connections to be broken. A DPR message with be sent as in the case of remove_transport/2.
Note!
Stopping a service does not remove any associated transports: remove_transport/2 must be called to remove transport configuration.
subscribe(SvcName) -> true
SvcName = service_name()
Subscribe to service_event()
messages from
a service.
It is not an error to subscribe to events from a service that does not yet exist. Doing so before adding transports is required to guarantee the reception of all transport-related events.