Module Libvirt

module Libvirt: sig .. end

OCaml bindings for libvirt.


Introduction and examples

This is a set of bindings for writing OCaml programs to manage virtual machines through libvirt.

Using libvirt interactively

Using the interactive toplevel:

$ ocaml -I +libvirt
        Objective Caml version 3.10.0

# #load "unix.cma";;
# #load "mllibvirt.cma";;
# let name = "test:///default";;
val name : string = "test:///default"
# let conn = Libvirt.Connect.connect_readonly ~name () ;;
val conn : Libvirt.ro Libvirt.Connect.t = <abstr>
# Libvirt.Connect.get_node_info conn;;
  : Libvirt.Connect.node_info =
{Libvirt.Connect.model = "i686"; Libvirt.Connect.memory = 3145728L;
 Libvirt.Connect.cpus = 16; Libvirt.Connect.mhz = 1400;
 Libvirt.Connect.nodes = 2; Libvirt.Connect.sockets = 2;
 Libvirt.Connect.cores = 2; Libvirt.Connect.threads = 2}

Compiling libvirt programs

This command compiles a program to native code:

ocamlopt -I +libvirt mllibvirt.cmxa list_domains.ml -o list_domains

Example: Connect to the hypervisor

The main modules are Libvirt.Connect, Libvirt.Domain and Libvirt.Network corresponding respectively to the virConnect*, virDomain*, and virNetwork* functions from libvirt. For brevity I usually rename these modules like this:

module C = Libvirt.Connect
module D = Libvirt.Domain
module N = Libvirt.Network

To get a connection handle, assuming a Xen hypervisor:

let name = "xen:///"
let conn = C.connect_readonly ~name ()

Example: List running domains

open Printf

let domains = D.get_domains conn [D.ListActive] in
List.iter (
  fun dom ->
    printf "%8d %s\n%!" (D.get_id dom) (D.get_name dom)
) domains;

Example: List inactive domains

let domains = D.get_domains conn [D.ListInactive] in
List.iter (
  fun dom ->
    printf "inactive %s\n%!" (D.get_name dom)
) domains;

Example: Print node info

let node_info = C.get_node_info conn in
printf "model = %s\n" node_info.C.model;
printf "memory = %Ld K\n" node_info.C.memory;
printf "cpus = %d\n" node_info.C.cpus;
printf "mhz = %d\n" node_info.C.mhz;
printf "nodes = %d\n" node_info.C.nodes;
printf "sockets = %d\n" node_info.C.sockets;
printf "cores = %d\n" node_info.C.cores;
printf "threads = %d\n%!" node_info.C.threads;

let hostname = C.get_hostname conn in
printf "hostname = %s\n%!" hostname;

let uri = C.get_uri conn in
printf "uri = %s\n%!" uri

Programming issues

General safety issues

Memory allocation / automatic garbage collection of all libvirt objects should be completely safe. If you find any safety issues or if your pure OCaml program ever segfaults, please contact the author.

You can force a libvirt object to be freed early by calling the Libvirt.Connect.close function on the object. This shouldn't affect the safety of garbage collection and should only be used when you want to explicitly free memory. Note that explicitly closing a connection object does nothing if there are still unclosed domain or network objects referencing it.

Note that even though you hold open (eg) a domain object, that doesn't mean that the domain (virtual machine) actually exists. The domain could have been shut down or deleted by another user. Thus domain objects can raise odd exceptions at any time. This is just the nature of virtualisation.

Backwards and forwards compatibility

OCaml-libvirt requires libvirt version 1.2.8 or later. Future releases of OCaml-libvirt will use newer features of libvirt and therefore will require later versions of libvirt. It is always possible to dynamically link your application against a newer libvirt than OCaml-libvirt was originally compiled against.

Get list of domains and domain infos

This is a very common operation, and libvirt supports various different methods to do it. We have hidden the complexity in a flexible Libvirt.Domain.get_domains and Libvirt.Domain.get_domains_and_infos calls which is easy to use and automatically chooses the most efficient method depending on the version of libvirt in use.

Threads

You can issue multiple concurrent libvirt requests in different threads. However you must follow this rule: Each thread must have its own separate libvirt connection, or you must implement your own mutex scheme to ensure that no two threads can ever make concurrent calls using the same libvirt connection.

(Note that multithreaded code is not well tested. If you find bugs please report them.)

Initialisation

Libvirt requires all callers to call virInitialize before using the library. This is done automatically for you by these bindings when the program starts up, and we believe that the way this is done is safe.

Reference

type uuid = string 

This is a "raw" UUID, ie. a packed string of bytes.

type xml = string 

Type of XML (an uninterpreted string of bytes). Use PXP, expat, xml-light, etc. if you want to do anything useful with the XML.

type filename = string 

A filename.

val get_version : ?driver:string -> unit -> int * int

get_version () returns the library version in the first part of the tuple, and 0 in the second part.

get_version ~driver () returns the library version in the first part of the tuple, and the version of the driver called driver in the second part.

The version numbers are encoded as major * 1_000_000 + minor * 1000 + release.

val uuid_length : int

Length of packed UUIDs.

val uuid_string_length : int

Length of UUID strings.

type rw = [ `R | `W ] 
type ro = [ `R ] 

These phantom types are used to ensure the type-safety of read-only versus read-write connections.

All connection/domain/etc. objects are marked with a phantom read-write or read-only type, and trying to pass a read-only object into a function which could mutate the object will cause a compile time error.

Each module provides a function like Libvirt.Connect.const to demote a read-write object into a read-only object. The opposite operation is, of course, not allowed.

If you want to handle both read-write and read-only connections at runtime, use a variant similar to this:

type conn_t =
    | No_connection
    | Read_only of Libvirt.ro Libvirt.Connect.t
    | Read_write of Libvirt.rw Libvirt.Connect.t

Forward definitions

These definitions are placed here to avoid the need to use recursive module dependencies.

Connections

module Connect: sig .. end

Module dealing with connections.

Domains

module Domain: sig .. end

Module dealing with domains.

module Event: sig .. end

Module dealing with events generated by domain state changes.

Networks

module Network: sig .. end

Module dealing with networks.

Storage pools

module Pool: sig .. end

Module dealing with storage pools.

Storage volumes

module Volume: sig .. end

Module dealing with storage volumes.

Secrets

module Secret: sig .. end

Module dealing with secrets.

Error handling and exceptions

module Virterror: sig .. end

Module dealing with errors.

exception Virterror of Virterror.t

This exception can be raised by any library function that detects an error. To get a printable error message, call Libvirt.Virterror.to_string on the content of this exception.

exception Not_supported of string

Functions may raise Not_supported "virFoo" (where virFoo is the libvirt function name) if a function is not supported at either compile or run time. This applies to any libvirt function added after version 0.2.1.

See also https://libvirt.org/hvsupport.html

Utility functions

val map_ignore_errors : ('a -> 'b) -> 'a list -> 'b list

map_ignore_errors f xs calls function f for each element of xs.

This is just like List.map except that if f x throws a Libvirt.Virterror.t exception, the error is ignored and f x is not returned in the final list.

This function is primarily useful when dealing with domains which might 'disappear' asynchronously from the currently running program.