econfd_maapi Module

An Erlang interface equivalent to the MAAPI C-API

This modules implements the Management Agent API. All functions in this module have an equivalent function in the C library. The actual semantics of each of the API functions described here is better described in the man page confd_lib_maapi(3).

Types

confd_user_identification/0

-type confd_user_identification() :: #confd_user_identification{}.

confd_user_info/0

-type confd_user_info() :: #confd_user_info{}.

dbname/0

-type dbname() :: 0 | 1 | 2 | 3 | 4 | 6 | 7.

The DB name can be either

  • 0 = CONFD_NO_DB

  • 1 = CONFD_CANDIDATE

  • 2 = CONFD_RUNNING

  • 3 = CONFD_STARTUP

  • 4 = CONFD_OPERATIONAL

  • 6 = CONFD_PRE_COMMIT_RUNNING

  • 7 = CONFD_INTENDED

Check maapi_start_trans() in confd_lib_maapi(3) for detailed information.

err/0

Errors can be either

  • {error, Ecode::integer(), Reason::binary()} where Ecode is one of the error codes defined in econfd_errors.hrl, and Reason is (possibly empty) textual description

  • {error, closed} if the socket gets closed

find_next_type/0

The type is used in find_next/3 can be either

  • 0 = CONFD_FIND_NEXT

  • 1 = CONFD_FIND_SAME_OR_NEXT

Check maapi_find_next() in confd_lib_maapi(3) for detailed information.

maapi_cursor/0

proto/0

The protocol to start user session can be either

  • 0 = CONFD_PROTO_UNKNOWN

  • 1 = CONFD_PROTO_TCP

  • 2 = CONFD_PROTO_SSH

  • 3 = CONFD_PROTO_SYSTEM

  • 4 = CONFD_PROTO_CONSOLE

  • 5 = CONFD_PROTO_SSL

  • 6 = CONFD_PROTO_HTTP

  • 7 = CONFD_PROTO_HTTPS

  • 8 = CONFD_PROTO_UDP

  • 9 = CONFD_PROTO_TLS

read_ret/0

Related types: econfd:transport_error()

template_type/0

The type is used in ncs_template_variables/3

  • 0 = DEVICE_TEMPLATE - Designates device template, device template means the specific template configuration name under /ncs:devices/ncs:template.

  • 1 = SERVICE_TEMPLATE - Designates service template, service template means the specific template configuration name of template loaded from the directory templates of the package.

  • 2 = COMPLIANCE_TEMPLATE - Designates compliance template, compliance template used to verify that the configuration on a device conforms to an expected, predefined configuration, it also means the specific template configuration name under /ncs:compliance/ncs:template

trans_mode/0

verbosity/0

The type is used in start_span_th/7 and can be either

  • 0 = CONFD_PROGRESS_NORMAL

  • 1 = CONFD_PROGRESS_VERBOSE

  • 2 = CONFD_PROGRESS_VERY_VERBOSE

  • 3 = CONFD_PROGRESS_DEBUG

Check maapi_start_span_th() in confd_lib_maapi(3) for detailed information.

xpath_eval_option/0

Related types: econfd:ikeypath()

Functions

aaa_reload/2

Related types: err(), econfd:socket()

Tell AAA to reload external AAA data.

abort_trans/2

Related types: err(), econfd:socket()

Abort transaction.

abort_upgrade/1

Related types: err(), econfd:socket()

Abort in-service upgrade.

aes256_key/1

aes_key/2

all_keys/2

all_keys/3

Related types: err(), econfd:ikeypath(), econfd:key(), econfd:socket()

Utility function. Return all keys in a list.

apply_trans/3

Related types: err(), econfd:socket()

Equivalent to apply_trans(Socket, Tid, KeepOpen, 0).

apply_trans/4

Related types: err(), econfd:socket()

Apply all in the transaction.

This is the combination of validate/prepare/commit done in the right order.

attach/3

Related types: err(), econfd:confd_trans_ctx(), econfd:namespace(), econfd:socket()

Attach to a running transaction.

Give NameSpace as 0 if it doesn't matter (-1 works too but is deprecated).

attach2/4

Related types: err(), econfd:namespace(), econfd:socket()

Attach to a running transaction. Give NameSpace as 0 if it doesn't matter (-1 works too but is deprecated).

attach_init/1

Related types: err(), econfd:socket()

Attach to the CDB init/upgrade transaction in phase0.

Returns the transaction handle to use in subsequent maapi calls on success.

authenticate/4

Related types: err(), econfd:socket()

Autenticate a user using ConfD AAA.

authenticate2/8

Related types: err(), econfd:ip(), econfd:socket()

Autenticate a user using ConfD AAA.

bool2int/1

candidate_abort_commit/1

Related types: err(), econfd:socket()

Equivalent to candidate_abort_commit(Socket, <<>>).

candidate_abort_commit/2

Related types: err(), econfd:socket()

Cancel persistent confirmed commit.

candidate_commit/1

Related types: err(), econfd:socket()

Equivalent to candidate_commit_info(Socket, undefined, <<>>, <<>>).

Copies candidate to running or confirms a confirmed commit.

candidate_commit/2

Related types: err(), econfd:socket()

Equivalent to candidate_commit_info(Socket, PersistId, <<>>, <<>>).

Confirms persistent confirmed commit.

candidate_commit_info/3

Related types: err(), econfd:socket()

Equivalent to candidate_commit_info(Socket, undefined, Label, Comment).

Like candidate_commit/1, but set the "Label" and/or "Comment" that is stored in the rollback file when the candidate is committed to running.

To set only the "Label", give Comment as an empty binary, and to set only the "Comment", give Label as an empty binary.

Note: To ensure that the "Label" and/or "Comment" are stored in the rollback file in all cases when doing a confirmed commit, they must be given both with the confirmed commit (using candidate_confirmed_commit_info/4) and with the confirming commit (using this function).

candidate_commit_info/4

Related types: err(), econfd:socket()

Combines candidate_commit/2 and candidate_commit_info/3 - set "Label" and/or "Comment" when confirming a persistent confirmed commit.

Note: To ensure that the "Label" and/or "Comment" are stored in the rollback file in all cases when doing a confirmed commit, they must be given both with the confirmed commit (using candidate_confirmed_commit_info/6) and with the confirming commit (using this function).

candidate_confirmed_commit/2

Related types: err(), econfd:socket()

Equivalent to candidate_confirmed_commit_info(Socket, TimeoutSecs, undefined, undefined, <<>>, <<>>).

Copy candidate into running, but rollback if not confirmed by a call of candidate_commit/1.

candidate_confirmed_commit/4

Related types: err(), econfd:socket()

Equivalent to candidate_confirmed_commit_info(Socket, TimeoutSecs, Persist, PersistId, <<>>, <<>>).

Starts or extends persistent confirmed commit.

candidate_confirmed_commit_info/4

Related types: err(), econfd:socket()

Equivalent to candidate_confirmed_commit_info(Socket, TimeoutSecs, undefined, undefined, Label, Comment).

Like candidate_confirmed_commit/2, but set the "Label" and/or "Comment" that is stored in the rollback file when the candidate is committed to running.

To set only the "Label", give Comment as an empty binary, and to set only the "Comment", give Label as an empty binary.

Note: To ensure that the "Label" and/or "Comment" are stored in the rollback file in all cases when doing a confirmed commit, they must be given both with the confirmed commit (using this function) and with the confirming commit (using candidate_commit_info/3).

candidate_confirmed_commit_info/6

Related types: err(), econfd:socket()

Combines candidate_confirmed_commit/4 and candidate_confirmed_commit_info/4 - set "Label" and/or "Comment" when starting or extending a persistent confirmed commit.

Note: To ensure that the "Label" and/or "Comment" are stored in the rollback file in all cases when doing a confirmed commit, they must be given both with the confirmed commit (using this function) and with the confirming commit (using candidate_commit_info/4).

candidate_reset/1

Related types: err(), econfd:socket()

Copy running into candidate.

candidate_validate/1

Related types: err(), econfd:socket()

Validate the candidate config.

cli_prompt/4

Related types: err(), econfd:socket()

Prompt CLI user for a reply.

cli_prompt/5

Related types: err(), econfd:socket()

Prompt CLI user for a reply - return error if no reply is received within Timeout seconds.

cli_prompt_oneof/4

Related types: err(), econfd:socket()

Prompt CLI user for a reply.

cli_prompt_oneof/5

Related types: err(), econfd:socket()

Prompt CLI user for a reply - return error if no reply is received within Timeout seconds.

cli_read_eof/3

Related types: err(), econfd:socket()

Read data from CLI until EOF.

cli_read_eof/4

Related types: err(), econfd:socket()

Read data from CLI until EOF - return error if no reply is received within Timeout seconds.

cli_write/3

Related types: err(), econfd:socket()

Write mesage to the CLI.

close/1

Related types: econfd:error_reason(), econfd:socket()

Close socket.

commit_trans/2

Related types: err(), econfd:socket()

Commit a transaction.

commit_upgrade/1

Related types: err(), econfd:socket()

Commit in-service upgrade.

confirmed_commit_in_progress/1

Related types: err(), econfd:socket()

Is a confirmed commit in progress.

connect/1

Related types: econfd:connect_result()

Connect a maapi socket to ConfD.

connect/2

Related types: econfd:connect_result(), econfd:ip()

Connect a maapi socket to ConfD.

copy/3

Related types: err(), econfd:socket()

Copy data from one transaction to another.

copy_running_to_startup/1

Related types: err(), econfd:socket()

Copy running to startup.

copy_tree/4

Related types: err(), econfd:ikeypath(), econfd:socket()

Copy an entire subtree in the configuration from one point to another.

create/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Create a new element.

delete/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Delete an element.

delete_config/2

Related types: dbname(), err(), econfd:socket()

Delete all data from a data store.

des_key/4

detach/2

Related types: err(), econfd:socket()

Detach from the transaction.

diff_iterate/4

Equivalent to diff_iterate(Sock, Tid, Fun, 0, InitState).

diff_iterate/5

Related types: econfd:socket()

Iterate through a diff.

This function is used in combination with the notifications API where we get a chance to iterate through the diff of a transaction just before it gets commited. The transaction hangs until we have called econfd_notif:notification_done/2. The function can also be called from within validate() callbacks to traverse a diff while validating. Currently OldValue is always the atom 'undefined'. When Op == ?MOP_MOVED_AFTER (only for "ordered-by user" list entry), Value == {} means that the entry was moved first in the list, otherwise Value is a econfd:key() tuple that identifies the entry it was moved after.

do_connect/1

end_progress_span/3

Related types: econfd:socket()

end_user_session/1

Related types: err(), econfd:socket()

Ends a user session.

exists/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Check if an element exists.

find_next/3

Related types: err(), find_next_type(), maapi_cursor(), econfd:key()

find the list entry matching Type and Key.

finish_trans/2

Related types: err(), econfd:socket()

Finish a transaction.

get_attrs/4

Related types: err(), econfd:ikeypath(), econfd:socket()

Get the selected attributes for an element.

Calling with an empty attribute list returns all attributes.

get_authorization_info/2

Related types: err(), econfd:socket()

Get authorization info for a user session.

get_case/4

Related types: err(), econfd:ikeypath(), econfd:qtag(), econfd:socket()

Get the current case for a choice.

get_elem/3

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Read an element.

get_elem_no_defaults/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Read an element, but return 'default' instead of the value if the default value is in effect.

get_mode/2

Related types: trans_mode(), econfd:socket()

Get the mode for the given transaction.

get_my_user_session_id/1

Related types: err(), econfd:socket()

Get my user session id.

get_next/1

Related types: err(), maapi_cursor(), econfd:key()

iterate through the entries of a list.

get_object/3

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Read all the values in a container or list entry.

get_objects/2

Related types: err(), maapi_cursor()

Read all the values for NumEntries list entries, starting at the point given by the cursor C.

The return value has one Erlang list for each YANG list entry, i.e. it is a list of at most NumEntries lists. If we reached the end of the YANG list, {done, Values} is returned, and there will be fewer than NumEntries lists in Values - otherwise {ok, C2, Values} is returned, where C2 can be used to continue the traversal.

get_rollback_id/2

Related types: econfd:socket()

Get rollback id of commited transaction.

get_running_db_status/1

Related types: err(), econfd:socket()

Get the "running status".

get_user_session/2

Related types: confd_user_info(), err(), econfd:socket()

Get session info for a user session.

get_user_sessions/1

Related types: err(), econfd:socket()

Get all user sessions.

get_values/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:tagval()

Read the values for the leafs that have the "value" 'not_found' in the Values list.

This can be used to read an arbitrary set of sub-elements of a container or list entry. The return value is a list of the same length as Values, i.e. the requested leafs are in the same position in the returned list as in the Values argument. The elements in the returned list are always "canonical" though, i.e. of the form econfd:tagval().

hide_group/3

Related types: err(), econfd:socket()

Do hide a hide group.

Hide all nodes belonging to a hide group in a transaction that started with flag FLAG_HIDE_ALL_HIDEGROUPS.

hkeypath2ikeypath/2

Related types: err(), econfd:socket()

Convert a hkeypath to an ikeypath.

ibool/1

init_cursor/3

Related types: maapi_cursor(), econfd:ikeypath(), econfd:socket()

Equivalent to init_cursor(Socket, Tik, IKeypath, undefined).

init_cursor/4

Related types: maapi_cursor(), econfd:ikeypath(), econfd:socket()

Initalize a get_next() cursor.

init_upgrade/3

Related types: err(), econfd:socket()

Start in-service upgrade.

insert/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Insert an entry in an integer-keyed list.

install_crypto_keys/1

Related types: err(), econfd:socket()

Fetch keys for the encrypted data types from the server.

Encrypted data type can be tailf:aes-cfb-128-encrypted-string and tailf:aes-256-cfb-128-encrypted-string.

is_candidate_modified/1

Related types: err(), econfd:socket()

Check if candidate has been modified.

is_lock_set/2

Related types: dbname(), err(), econfd:socket()

Check if a db is locked or not.

Return 0 or the Usid of the lock owner.

is_running_modified/1

Related types: err(), econfd:socket()

Check if running has been modified since the last copy to startup was done.

iterate/6

Related types: econfd:ikeypath(), econfd:socket()

Iterate over all the data in the transaction and the underlying data store.

Flags can be given as ?MAAPI_ITER_WANT_ATTR to request that attributes (if any) are passed to the Fun, otherwise it should be 0. The possible values for Ret in the return value for Fun are the same as for diff_iterate/5.

iterate_result/3

keypath_diff_iterate/5

Related types: econfd:ikeypath(), econfd:socket()

Iterate through a diff.

This function behaves like diff_iterate/5 with the exception that the provided keypath IKP, prunes the tree and only diffs below that path are considered.

keypath_diff_iterate/6

kill_user_session/2

Related types: err(), econfd:socket()

Kill a user session.

lock/2

Related types: dbname(), err(), econfd:socket()

Lock a database.

lock_partial/3

Related types: dbname(), err(), econfd:socket()

Request a partial lock on a database.

The set of nodes to lock is specified as a list of XPath expressions.

mk_uident/1

move/4

Related types: err(), econfd:ikeypath(), econfd:key(), econfd:socket()

Move (rename) an entry in a list.

move_ordered/4

Related types: err(), econfd:ikeypath(), econfd:key(), econfd:socket()

Move an entry in an "ordered-by user" list.

ncs_apply_template/7

Related types: err(), econfd:ikeypath(), econfd:socket()

Apply a template that has been loaded into NCS.

The TemplateName parameter gives the name of the template. The Variables parameter is a list of variables and names for substitution into the template.

ncs_apply_trans_params/4

Related types: err(), econfd:socket(), econfd:tagval()

Apply transaction with commit parameters.

This is a version of apply_trans that takes commit parameters in form of a list of tagged values according to the input parameters for rpc prepare-transaction as defined in tailf-netconf-ncs.yang module. The result of this function may include a list of tagged values according to the output parameters of rpc prepare-transaction or output parameters of rpc commit-transaction as defined in tailf-netconf-ncs.yang module.

ncs_get_trans_params/2

Related types: err(), econfd:socket(), econfd:tagval()

Get transaction commit parameters.

ncs_template_variables/2

Related types: err(), econfd:socket()

Retrieve the variables used in a template.

ncs_template_variables/3

Related types: err(), template_type(), econfd:socket()

Retrieve the variables used in a template.

ncs_templates/1

Related types: err(), econfd:socket()

Retrieve a list of the templates currently loaded into NCS.

ncs_write_service_log_entry/5

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Write a service log entry.

netconf_ssh_call_home/3

Related types: err(), econfd:ip(), econfd:socket()

netconf_ssh_call_home_opaque/4

Related types: err(), econfd:ip(), econfd:socket()

num_instances/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Find the number of entries in a list.

perform_upgrade/2

Related types: err(), econfd:socket()

Do in-service upgrade.

prepare_trans/2

Related types: err(), econfd:socket()

Equivalent to prepare_trans(Socket, Tid, 0).

prepare_trans/3

Related types: err(), econfd:socket()

Prepare for commit.

prio_message/3

Related types: err(), econfd:socket()

Write priority message.

progress_info/6

Related types: verbosity(), econfd:ikeypath(), econfd:socket()

progress_info_th/7

Related types: verbosity(), econfd:ikeypath(), econfd:socket()

reload_config/1

Related types: err(), econfd:socket()

Tell ConfD daemon to reload its configuration.

request_action/3

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:tagval()

Invoke an action defined in the data model.

request_action_th/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:tagval()

Invoke an action defined in the data model using the provided transaction.

Does the same thing as request_action/3, but uses the current namespace, the path position, and the user session from the transaction indicated by the 'Tid' handle.

reverse/1

revert/2

Related types: err(), econfd:socket()

Remove all changes in the transaction.

set_attr/5

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Set the an attribute for an element. Value == undefined means that the attribute should be deleted.

set_comment/3

Related types: err(), econfd:socket()

Set the "Comment" that is stored in the rollback file when a transaction towards running is committed.

set_delayed_when/3

Related types: err(), econfd:socket()

Enable/disable the "delayed when" mode for a transaction.

Returns the old setting on success.

set_elem/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Write an element.

set_elem2/4

Related types: err(), econfd:ikeypath(), econfd:socket()

Write an element using the textual value representation.

set_flags/3

Related types: err(), econfd:socket()

Change flag settings for a transaction.

See ?MAAPI_FLAG_XXX in econfd.hrl for the available flags, however ?MAAPI_FLAG_HIDE_INACTIVE ?MAAPI_FLAG_DELAYED_WHEN and ?MAAPI_FLAG_HIDE_ALL_HIDEGROUPS cannot be changed after transaction start (but see set_delayed_when/3).

set_label/3

Related types: err(), econfd:socket()

Set the "Label" that is stored in the rollback file when a transaction towards running is committed.

set_object/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Write an entire object, i.e. YANG list entry or container.

set_readonly_mode/2

Related types: err(), econfd:socket()

Control if we can create rw transactions.

set_running_db_status/2

Related types: err(), econfd:socket()

Set the "running status".

set_user_session/2

Related types: err(), econfd:socket()

Assign a user session.

set_values/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:tagval()

Write a list of tagged values.

This function is an alternative to set_object/4, and allows for writing more complex structures (e.g. multiple entries in a list).

shared_create/3

Related types: err(), econfd:ikeypath(), econfd:socket()

Create a new element, and also set an attribute indicating how many times this element has been created.

shared_set_elem/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:value()

Write an element from NCS FastMap.

shared_set_elem2/4

Related types: err(), econfd:ikeypath(), econfd:socket()

Write an element using the textual value representation from NCS fastmap.

shared_set_values/4

Related types: err(), econfd:ikeypath(), econfd:socket(), econfd:tagval()

Write a list of tagged values from NCS FastMap.

snmpa_reload/2

Related types: err(), econfd:socket()

Tell ConfD to reload external SNMP Agent config data.

start_phase/3

Related types: err(), econfd:socket()

Tell ConfD to proceed to next start phase.

start_progress_span/6

Related types: verbosity(), econfd:ikeypath(), econfd:socket()

start_progress_span_th/7

Related types: verbosity(), econfd:ikeypath(), econfd:socket()

start_trans/3

Related types: dbname(), err(), econfd:socket()

Start a new transaction.

start_trans/4

Related types: dbname(), err(), econfd:socket()

Start a new transaction within an existing user session.

start_trans/5

Related types: dbname(), err(), econfd:socket()

Start a new transaction within an existing user session and/or with flags.

See ?MAAPI_FLAG_XXX in econfd.hrl for the available flags. To use the existing user session of the socket, give Usid = 0.

start_trans/6

start_trans_in_trans/4

Related types: err(), econfd:socket()

Start a new transaction with an existing transaction as backend.

To use the existing user session of the socket, give Usid = 0.

start_trans_in_trans/5

Related types: err(), econfd:socket()

Start a new transaction with an existing transaction as backend.

To use the existing user session of the socket, give Usid = 0.

start_user_session/6

Related types: err(), proto(), econfd:ip(), econfd:socket()

Equivalent to start_user_session(Socket, UserName, Context, Groups, SrcIp, 0, Proto).

start_user_session/7

Related types: err(), proto(), econfd:ip(), econfd:socket()

Equivalent to start_user_session(Socket, UserName, Context, Groups, SrcIp, 0, Proto, undefined).

start_user_session/8

Related types: confd_user_identification(), err(), proto(), econfd:ip(), econfd:socket()

Initiate a new maapi user session.

returns a maapi session id. Before we can execute any maapi functions we must always have an associated user session.

stop/1

Related types: econfd:socket()

Equivalent to stop(Sock, true).

Tell ConfD daemon to stop, returns when daemon has exited.

stop/2

Related types: econfd:socket()

Tell ConfD daemon to stop, if Synchronous is true won't return until daemon has come to a halt.

Note that the socket will most certainly not be possible to use again, since ConfD will close its end when it exits.

sys_message/3

Related types: err(), econfd:socket()

Write system message.

unhide_group/3

Related types: err(), econfd:socket()

Do unhide a hide group.

Unhide all nodes belonging to a hide group in a transaction that started with flag FLAG_HIDE_ALL_HIDEGROUPS.

unlock/2

Related types: dbname(), err(), econfd:socket()

Unlock a database.

unlock_partial/2

Related types: err(), econfd:socket()

Remove the partial lock identified by LockId.

user_message/4

Related types: err(), econfd:socket()

Write user message.

validate_trans/4

Related types: err(), econfd:socket()

Validate the transaction.

wait_start/1

Related types: err(), econfd:socket()

Equivalent to wait_start(Socket, 2).

Wait until ConfD daemon has completely started.

wait_start/2

Related types: err(), econfd:socket()

Wait until ConfD daemon has reached a certain start phase.

xpath_eval/6

Related types: err(), xpath_eval_option(), econfd:socket()

Evaluate the XPath expression Expr, invoking ResultFun for each node in the resulting node set.

The possible values for Ret in the return value for ResultFun are ?ITER_CONTINUE and ?ITER_STOP.

xpath_eval/7

Related types: econfd:ikeypath(), econfd:socket()

Evaluate the XPath expression Expr, invoking ResultFun for each node in the resulting node set.

The possible values for Ret in the return value for ResultFun are ?ITER_CONTINUE and ?ITER_STOP.

xpath_eval_expr/4

Related types: err(), xpath_eval_option(), econfd:socket()

Evaluate the XPath expression Expr, returning the result as a string.

xpath_eval_expr/5

Related types: err(), econfd:ikeypath(), econfd:socket()

Evaluate the XPath expression Expr, returning the result as a string.

xpath_eval_expr_loop/2

xpath_eval_loop/4

Last updated

Was this helpful?