Module Libvirt.Connect

module Connect: sig .. end

Module dealing with connections. Connect.t is the connection object.


type 'rw t 

Connection. Read-only connections have type ro Connect.t and read-write connections have type rw Connect.t.

type node_info = {
   model : string; (*

CPU model

*)
   memory : int64; (*

memory size in kilobytes

*)
   cpus : int; (*

number of active CPUs

*)
   mhz : int; (*

expected CPU frequency

*)
   nodes : int; (*

number of NUMA nodes (1 = UMA)

*)
   sockets : int; (*

number of CPU sockets per node

*)
   cores : int; (*

number of cores per socket

*)
   threads : int; (*

number of threads per core

*)
}
type credential_type = 
| CredentialUsername (*

Identity to act as

*)
| CredentialAuthname (*

Identify to authorize as

*)
| CredentialLanguage (*

RFC 1766 languages, comma separated

*)
| CredentialCnonce (*

client supplies a nonce

*)
| CredentialPassphrase (*

Passphrase secret

*)
| CredentialEchoprompt (*

Challenge response

*)
| CredentialNoechoprompt (*

Challenge response

*)
| CredentialRealm (*

Authentication realm

*)
| CredentialExternal (*

Externally managed credential

*)
type credential = {
   typ : credential_type; (*

The type of credential

*)
   prompt : string; (*

Prompt to show to user

*)
   challenge : string option; (*

Additional challenge to show

*)
   defresult : string option; (*

Optional default result

*)
}
type auth = {
   credtype : credential_type list; (*

List of supported credential_type values

*)
   cb : credential list -> string option list; (*

Callback used to collect credentials.

The input is a list of all the requested credentials.

The function returns a list of all the results from the requested credentials, so the number of results must match the number of input credentials. Each result is optional, and in case it is None it means there was no result.

*)
}
val connect : ?name:string -> unit -> Libvirt.rw t

connect ~name () connects to the hypervisor with URI name.

connect () connects to the default hypervisor.

val connect_readonly : ?name:string -> unit -> Libvirt.ro t

connect_readonly ~name () connects in read-only mode to the hypervisor with URI name.

connect_readonly () connects in read-only mode to the default hypervisor.

val connect_auth : ?name:string -> auth -> Libvirt.rw t

connect_auth ~name auth connects to the hypervisor with URI name, using auth as authentication handler.

connect_auth auth connects to the default hypervisor, using auth as authentication handler.

val connect_auth_readonly : ?name:string -> auth -> Libvirt.ro t

connect_auth_readonly ~name auth connects in read-only mode to the hypervisor with URI name, using auth as authentication handler.

connect_auth_readonly auth connects in read-only mode to the default hypervisor, using auth as authentication handler.

val close : [> `R ] t -> unit

close conn closes and frees the connection object in memory.

The connection is automatically closed if it is garbage collected. This function just forces it to be closed and freed right away.

val get_type : [> `R ] t -> string

Returns the name of the driver (hypervisor).

val get_version : [> `R ] t -> int

Returns the driver version major * 1_000_000 + minor * 1000 + release

val get_hostname : [> `R ] t -> string

Returns the hostname of the physical server.

val get_uri : [> `R ] t -> string

Returns the canonical connection URI.

val get_max_vcpus : [> `R ] t -> ?type_:string -> unit -> int

Returns the maximum number of virtual CPUs supported by a guest VM of a particular type.

val list_domains : [> `R ] t -> int -> int array

list_domains conn max returns the running domain IDs, up to a maximum of max entries.

Call Libvirt.Connect.num_of_domains first to get a value for max.

See also: Libvirt.Domain.get_domains, Libvirt.Domain.get_domains_and_infos.

val num_of_domains : [> `R ] t -> int

Returns the number of running domains.

val get_capabilities : [> `R ] t -> Libvirt.xml

Returns the hypervisor capabilities (as XML).

val num_of_defined_domains : [> `R ] t -> int

Returns the number of inactive (shutdown) domains.

val list_defined_domains : [> `R ] t -> int -> string array

list_defined_domains conn max returns the names of the inactive domains, up to a maximum of max entries.

Call Libvirt.Connect.num_of_defined_domains first to get a value for max.

See also: Libvirt.Domain.get_domains, Libvirt.Domain.get_domains_and_infos.

val num_of_networks : [> `R ] t -> int

Returns the number of networks.

val list_networks : [> `R ] t -> int -> string array

list_networks conn max returns the names of the networks, up to a maximum of max entries. Call Libvirt.Connect.num_of_networks first to get a value for max.

val num_of_defined_networks : [> `R ] t -> int

Returns the number of inactive networks.

val list_defined_networks : [> `R ] t -> int -> string array

list_defined_networks conn max returns the names of the inactive networks, up to a maximum of max entries. Call Libvirt.Connect.num_of_defined_networks first to get a value for max.

val num_of_pools : [> `R ] t -> int

Returns the number of storage pools.

val list_pools : [> `R ] t -> int -> string array

Return list of storage pools.

val num_of_defined_pools : [> `R ] t -> int

Returns the number of storage pools.

val list_defined_pools : [> `R ] t -> int -> string array

Return list of storage pools.

val num_of_secrets : [> `R ] t -> int

Returns the number of secrets.

val list_secrets : [> `R ] t -> int -> string array

Returns the list of secrets.

val get_node_info : [> `R ] t -> node_info

Return information about the physical server.

val node_get_free_memory : [> `R ] t -> int64

node_get_free_memory conn returns the amount of free memory (not allocated to any guest) in the machine.

val node_get_cells_free_memory : [> `R ] t -> int -> int -> int64 array

node_get_cells_free_memory conn start max returns the amount of free memory on each NUMA cell in kilobytes. start is the first cell for which we return free memory. max is the maximum number of cells for which we return free memory. Returns an array of up to max entries in length.

val maxcpus_of_node_info : node_info -> int

Calculate the total number of CPUs supported (but not necessarily active) in the host.

val cpumaplen : int -> int

Calculate the length (in bytes) required to store the complete CPU map between a single virtual and all physical CPUs of a domain.

val use_cpu : bytes -> int -> unit

use_cpu cpumap cpu marks cpu as usable in cpumap.

val unuse_cpu : bytes -> int -> unit

unuse_cpu cpumap cpu marks cpu as not usable in cpumap.

val cpu_usable : bytes -> int -> int -> int -> bool

cpu_usable cpumaps maplen vcpu cpu checks returns true iff the cpu is usable by vcpu.

val set_keep_alive : [> `R ] t -> int -> int -> unit

set_keep_alive conn interval count starts sending keepalive messages after interval seconds of inactivity and consider the connection to be broken when no response is received after count keepalive messages. Note: the client has to implement and run an event loop to be able to use keep-alive messages.

val get_auth_default : unit -> auth

get_auth_default () returns the default authentication handler of libvirt.

val get_domain_capabilities : ?emulatorbin:string ->
?arch:string ->
?machine:string -> ?virttype:string -> [> `R ] t -> string

get_domain_capabilities () returns the XML with the available capabilities of the emulator or libvirt for domains.

The optional flag ?emulatorbin is used to specify a different emulator.

The optional flag ?arch is used to specify a different architecture.

The optional flag ?machine is used to specify a different machine type.

The optional flag ?virttype is used to specify a different type of virtualization.

val const : [> `R ] t -> Libvirt.ro t

const conn turns a read/write connection into a read-only connection. Note that the opposite operation is impossible.