Module Libvirt.Domain

module Domain: sig .. end

Module dealing with domains. Domain.t is the domain object.


type 'rw t 

Domain handle. Read-only handles have type ro Domain.t and read-write handles have type rw Domain.t.

type state = 
| InfoNoState
| InfoRunning
| InfoBlocked
| InfoPaused
| InfoShutdown
| InfoShutoff
| InfoCrashed
| InfoPMSuspended
type info = {
   state : state; (*

running state

*)
   max_mem : int64; (*

maximum memory in kilobytes

*)
   memory : int64; (*

memory used in kilobytes

*)
   nr_virt_cpu : int; (*

number of virtual CPUs

*)
   cpu_time : int64; (*

CPU time used in nanoseconds

*)
}
type vcpu_state = 
| VcpuOffline
| VcpuRunning
| VcpuBlocked
type vcpu_info = {
   number : int; (*

virtual CPU number

*)
   vcpu_state : vcpu_state; (*

state

*)
   vcpu_time : int64; (*

CPU time used in nanoseconds

*)
   cpu : int; (*

real CPU number, -1 if offline

*)
}
type domain_create_flag = 
| START_PAUSED (*

Launch guest in paused state

*)
| START_AUTODESTROY (*

Automatically kill guest on close

*)
| START_BYPASS_CACHE (*

Avoid filesystem cache pollution

*)
| START_FORCE_BOOT (*

Discard any managed save

*)
| START_VALIDATE (*

Validate XML against schema

*)
type domain_device_modify_flag = 
| DEVICE_MODIFY_LIVE (*

Affect running domain state

*)
| DEVICE_MODIFY_CONFIG (*

Affect persistent domain state

*)
| DEVICE_MODIFY_FORCE (*

Affect running domain state forcedly

*)
type sched_param = string * sched_param_value 
type sched_param_value = 
| SchedFieldInt32 of int32
| SchedFieldUInt32 of int32
| SchedFieldInt64 of int64
| SchedFieldUInt64 of int64
| SchedFieldFloat of float
| SchedFieldBool of bool
type typed_param = string * typed_param_value 
type typed_param_value = 
| TypedFieldInt32 of int32
| TypedFieldUInt32 of int32
| TypedFieldInt64 of int64
| TypedFieldUInt64 of int64
| TypedFieldFloat of float
| TypedFieldBool of bool
| TypedFieldString of string
type migrate_flag = 
| Live
type memory_flag = 
| Virtual
type list_flag = 
| ListActive
| ListInactive
| ListAll
type block_stats = {
   rd_req : int64;
   rd_bytes : int64;
   wr_req : int64;
   wr_bytes : int64;
   errs : int64;
}
type interface_stats = {
   rx_bytes : int64;
   rx_packets : int64;
   rx_errs : int64;
   rx_drop : int64;
   tx_bytes : int64;
   tx_packets : int64;
   tx_errs : int64;
   tx_drop : int64;
}
type get_all_domain_stats_flag = 
| GetAllDomainsStatsActive
| GetAllDomainsStatsInactive
| GetAllDomainsStatsOther
| GetAllDomainsStatsPaused
| GetAllDomainsStatsPersistent
| GetAllDomainsStatsRunning
| GetAllDomainsStatsShutoff
| GetAllDomainsStatsTransient
| GetAllDomainsStatsBacking
| GetAllDomainsStatsEnforceStats
type stats_type = 
| StatsState
| StatsCpuTotal
| StatsBalloon
| StatsVcpu
| StatsInterface
| StatsBlock
| StatsPerf
type domain_stats_record = {
   dom_uuid : Libvirt.uuid;
   params : typed_param array;
}
type xml_desc_flag = 
| XmlSecure (*

dump security sensitive information too

*)
| XmlInactive (*

dump inactive domain information

*)
| XmlUpdateCPU (*

update guest CPU requirements according to host CPU

*)
| XmlMigratable (*

dump XML suitable for migration

*)
val max_peek : [> `R ] t -> int

Maximum size supported by the Libvirt.Domain.block_peek and Libvirt.Domain.memory_peek functions. If you want to peek more than this then you must break your request into chunks.

val create_linux : [> `W ] Libvirt.Connect.t -> Libvirt.xml -> Libvirt.rw t
Deprecated. Use Libvirt.Domain.create_xml instead.

Create a new guest domain (not necessarily a Linux one) from the given XML.

val create_xml : [> `W ] Libvirt.Connect.t ->
Libvirt.xml ->
domain_create_flag list -> Libvirt.rw t

Create a new guest domain from the given XML.

val lookup_by_id : 'a Libvirt.Connect.t -> int -> 'a t

Lookup a domain by ID.

val lookup_by_uuid : 'a Libvirt.Connect.t -> Libvirt.uuid -> 'a t

Lookup a domain by UUID. This uses the packed byte array UUID.

val lookup_by_uuid_string : 'a Libvirt.Connect.t -> string -> 'a t

Lookup a domain by (string) UUID.

val lookup_by_name : 'a Libvirt.Connect.t -> string -> 'a t

Lookup a domain by name.

val destroy : [> `W ] t -> unit

Abruptly destroy a domain.

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

free domain frees the domain object in memory.

The domain object is automatically freed if it is garbage collected. This function just forces it to be freed right away.

val suspend : [> `W ] t -> unit

Suspend a domain.

val resume : [> `W ] t -> unit

Resume a domain.

val save : [> `W ] t -> Libvirt.filename -> unit

Suspend a domain, then save it to the file.

val restore : [> `W ] Libvirt.Connect.t -> Libvirt.filename -> unit

Restore a domain from a file.

val core_dump : [> `W ] t -> Libvirt.filename -> unit

Force a domain to core dump to the named file.

val shutdown : [> `W ] t -> unit

Shutdown a domain.

val reboot : [> `W ] t -> unit

Reboot a domain.

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

Get the domain name.

val get_uuid : [> `R ] t -> Libvirt.uuid

Get the domain UUID (as a packed byte array).

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

Get the domain UUID (as a printable string).

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

get_id dom returns the ID of the domain. In most cases this returns -1 if the domain is not running.

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

Get the operating system type.

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

Get the maximum memory allocation.

val set_max_memory : [> `W ] t -> int64 -> unit

Set the maximum memory allocation.

val set_memory : [> `W ] t -> int64 -> unit

Set the normal memory allocation.

val get_info : [> `R ] t -> info

Get information about a domain.

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

Get the XML description of a domain.

val get_xml_desc_flags : [> `W ] t -> xml_desc_flag list -> Libvirt.xml

Get the XML description of a domain, with the possibility to specify flags.

val get_scheduler_type : [> `R ] t -> string * int

Get the scheduler type.

val get_scheduler_parameters : [> `R ] t -> int -> sched_param array

Get the array of scheduler parameters.

val set_scheduler_parameters : [> `W ] t -> sched_param array -> unit

Set the array of scheduler parameters.

val define_xml : [> `W ] Libvirt.Connect.t -> Libvirt.xml -> Libvirt.rw t

Define a new domain (but don't start it up) from the XML.

val undefine : [> `W ] t -> unit

Undefine a domain - removes its configuration.

val create : [> `W ] t -> unit

Launch a defined (inactive) domain.

val get_autostart : [> `R ] t -> bool

Get the autostart flag for a domain.

val set_autostart : [> `W ] t -> bool -> unit

Set the autostart flag for a domain.

val set_vcpus : [> `W ] t -> int -> unit

Change the number of vCPUs available to a domain.

val pin_vcpu : [> `W ] t -> int -> string -> unit

pin_vcpu dom vcpu bitmap pins a domain vCPU to a bitmap of physical CPUs. See the libvirt documentation for details of the layout of the bitmap.

val get_vcpus : [> `R ] t ->
int -> int -> int * vcpu_info array * string

get_vcpus dom maxinfo maplen returns the pinning information for a domain. See the libvirt documentation for details of the array and bitmap returned from this function.

val get_cpu_stats : [> `R ] t -> typed_param list array

get_pcpu_stats dom returns the physical CPU stats for a domain. See the libvirt documentation for details.

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

Returns the maximum number of vCPUs supported for this domain.

val attach_device : [> `W ] t -> Libvirt.xml -> unit

Attach a device (described by the device XML) to a domain.

val detach_device : [> `W ] t -> Libvirt.xml -> unit

Detach a device (described by the device XML) from a domain.

val detach_device_flags : [> `W ] t ->
Libvirt.xml -> domain_device_modify_flag list -> unit

Detach a device (described by the device XML) from a domain, with the possibility to specify flags.

val migrate : [> `W ] t ->
[> `W ] Libvirt.Connect.t ->
migrate_flag list ->
?dname:string ->
?uri:string -> ?bandwidth:int -> unit -> Libvirt.rw t

migrate dom dconn flags () migrates a domain to a destination host described by dconn.

The optional flag ?dname is used to rename the domain.

The optional flag ?uri is used to route the migration.

The optional flag ?bandwidth is used to limit the bandwidth used for migration (in Mbps).

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

Returns block device stats.

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

Returns network interface stats.

val block_peek : [> `W ] t -> string -> int64 -> int -> bytes -> int -> unit

block_peek dom path offset size buf boff reads size bytes at offset in the domain's path block device.

If successful then the data is written into buf starting at offset boff, for size bytes.

See also Libvirt.Domain.max_peek.

val memory_peek : [> `W ] t ->
memory_flag list -> int64 -> int -> bytes -> int -> unit

memory_peek dom Virtual offset size reads size bytes at offset in the domain's virtual memory.

If successful then the data is written into buf starting at offset boff, for size bytes.

See also Libvirt.Domain.max_peek.

val get_all_domain_stats : [> `R ] Libvirt.Connect.t ->
stats_type list ->
get_all_domain_stats_flag list ->
domain_stats_record array

get_all_domain_stats conn stats flags allows you to read all stats across multiple/all domains in a single call.

See the libvirt documentation for virConnectGetAllDomainStats.

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

const dom turns a read/write domain handle into a read-only domain handle. Note that the opposite operation is impossible.

val get_domains : ([> `R ] as 'a) Libvirt.Connect.t ->
list_flag list -> 'a t list

Get the active and/or inactive domains using the most efficient method available.

See also: Libvirt.Domain.get_domains_and_infos, Libvirt.Connect.list_domains, Libvirt.Connect.list_defined_domains.

val get_domains_and_infos : ([> `R ] as 'a) Libvirt.Connect.t ->
list_flag list ->
('a t * info) list

This gets the active and/or inactive domains and the domain info for each one using the most efficient method available.

See also: Libvirt.Domain.get_domains, Libvirt.Connect.list_domains, Libvirt.Connect.list_defined_domains, Libvirt.Domain.get_info.