ec8c9e85d4ca9ce2b733a067a9017be34429fb2e
[ocaml-libvirt.git] / libvirt / libvirt.ml
1 (* OCaml bindings for libvirt.
2    (C) Copyright 2007 Richard W.M. Jones, Red Hat Inc.
3    http://libvirt.org/
4
5    This library is free software; you can redistribute it and/or
6    modify it under the terms of the GNU Lesser General Public
7    License as published by the Free Software Foundation; either
8    version 2 of the License, or (at your option) any later version,
9    with the OCaml linking exception described in ../COPYING.LIB.
10
11    This library is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
14    Lesser General Public License for more details.
15
16    You should have received a copy of the GNU Lesser General Public
17    License along with this library; if not, write to the Free Software
18    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301  USA
19 *)
20
21 type uuid = string
22
23 type xml = string
24
25 type filename = string
26
27 external get_version : ?driver:string -> unit -> int * int = "ocaml_libvirt_get_version"
28
29 let uuid_length = 16
30 let uuid_string_length = 36
31
32 (* http://caml.inria.fr/pub/ml-archives/caml-list/2004/07/80683af867cce6bf8fff273973f70c95.en.html *)
33 type rw = [`R|`W]
34 type ro = [`R]
35
36 type ('a, 'b) job_t
37
38 module Connect =
39 struct
40   type 'rw t
41
42   type node_info = {
43     model : string;
44     memory : int64;
45     cpus : int;
46     mhz : int;
47     nodes : int;
48     sockets : int;
49     cores : int;
50     threads : int;
51   }
52
53   type list_flag =
54     | ListNoState | ListRunning | ListBlocked
55     | ListPaused | ListShutdown | ListShutoff | ListCrashed
56     | ListActive
57     | ListInactive
58     | ListAll
59
60   external connect : ?name:string -> unit -> rw t = "ocaml_libvirt_connect_open"
61   external connect_readonly : ?name:string -> unit -> ro t = "ocaml_libvirt_connect_open_readonly"
62   external close : [>`R] t -> unit = "ocaml_libvirt_connect_close"
63   external get_type : [>`R] t -> string = "ocaml_libvirt_connect_get_type"
64   external get_version : [>`R] t -> int = "ocaml_libvirt_connect_get_version"
65   external get_hostname : [>`R] t -> string = "ocaml_libvirt_connect_get_hostname"
66   external get_uri : [>`R] t -> string = "ocaml_libvirt_connect_get_uri"
67   external get_max_vcpus : [>`R] t -> ?type_:string -> unit -> int = "ocaml_libvirt_connect_get_max_vcpus"
68   external list_domains : [>`R] t -> int -> int array = "ocaml_libvirt_connect_list_domains"
69   external num_of_domains : [>`R] t -> int = "ocaml_libvirt_connect_num_of_domains"
70   external get_capabilities : [>`R] t -> xml = "ocaml_libvirt_connect_get_capabilities"
71   external num_of_defined_domains : [>`R] t -> int = "ocaml_libvirt_connect_num_of_defined_domains"
72   external list_defined_domains : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_defined_domains"
73   external num_of_networks : [>`R] t -> int = "ocaml_libvirt_connect_num_of_networks"
74   external list_networks : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_networks"
75   external num_of_defined_networks : [>`R] t -> int = "ocaml_libvirt_connect_num_of_defined_networks"
76   external list_defined_networks : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_defined_networks"
77   external num_of_pools : [>`R] t -> int = "ocaml_libvirt_connect_num_of_storage_pools"
78   external list_pools : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_storage_pools"
79   external num_of_defined_pools : [>`R] t -> int = "ocaml_libvirt_connect_num_of_defined_storage_pools"
80   external list_defined_pools : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_defined_storage_pools"
81
82   external get_node_info : [>`R] t -> node_info = "ocaml_libvirt_connect_get_node_info"
83   external node_get_free_memory : [> `R] t -> int64 = "ocaml_libvirt_connect_node_get_free_memory"
84   external node_get_cells_free_memory : [> `R] t -> int -> int -> int64 array = "ocaml_libvirt_connect_node_get_cells_free_memory"
85
86   (* See VIR_NODEINFO_MAXCPUS macro defined in <libvirt.h>. *)
87   let maxcpus_of_node_info { nodes = nodes; sockets = sockets;
88                              cores = cores; threads = threads } =
89     nodes * sockets * cores * threads
90
91   (* See VIR_CPU_MAPLEN macro defined in <libvirt.h>. *)
92   let cpumaplen nr_cpus =
93     (nr_cpus + 7) / 8
94
95   (* See VIR_USE_CPU, VIR_UNUSE_CPU, VIR_CPU_USABLE macros defined in <libvirt.h>. *)
96   let use_cpu cpumap cpu =
97     cpumap.[cpu/8] <-
98       Char.chr (Char.code cpumap.[cpu/8] lor (1 lsl (cpu mod 8)))
99   let unuse_cpu cpumap cpu =
100     cpumap.[cpu/8] <-
101       Char.chr (Char.code cpumap.[cpu/8] land (lnot (1 lsl (cpu mod 8))))
102   let cpu_usable cpumaps maplen vcpu cpu =
103     Char.code cpumaps.[vcpu*maplen + cpu/8] land (1 lsl (cpu mod 8)) <> 0
104
105   external const : [>`R] t -> ro t = "%identity"
106 end
107
108 module Virterror =
109 struct
110   type code =
111     | VIR_ERR_OK
112     | VIR_ERR_INTERNAL_ERROR
113     | VIR_ERR_NO_MEMORY
114     | VIR_ERR_NO_SUPPORT
115     | VIR_ERR_UNKNOWN_HOST
116     | VIR_ERR_NO_CONNECT
117     | VIR_ERR_INVALID_CONN
118     | VIR_ERR_INVALID_DOMAIN
119     | VIR_ERR_INVALID_ARG
120     | VIR_ERR_OPERATION_FAILED
121     | VIR_ERR_GET_FAILED
122     | VIR_ERR_POST_FAILED
123     | VIR_ERR_HTTP_ERROR
124     | VIR_ERR_SEXPR_SERIAL
125     | VIR_ERR_NO_XEN
126     | VIR_ERR_XEN_CALL
127     | VIR_ERR_OS_TYPE
128     | VIR_ERR_NO_KERNEL
129     | VIR_ERR_NO_ROOT
130     | VIR_ERR_NO_SOURCE
131     | VIR_ERR_NO_TARGET
132     | VIR_ERR_NO_NAME
133     | VIR_ERR_NO_OS
134     | VIR_ERR_NO_DEVICE
135     | VIR_ERR_NO_XENSTORE
136     | VIR_ERR_DRIVER_FULL
137     | VIR_ERR_CALL_FAILED
138     | VIR_ERR_XML_ERROR
139     | VIR_ERR_DOM_EXIST
140     | VIR_ERR_OPERATION_DENIED
141     | VIR_ERR_OPEN_FAILED
142     | VIR_ERR_READ_FAILED
143     | VIR_ERR_PARSE_FAILED
144     | VIR_ERR_CONF_SYNTAX
145     | VIR_ERR_WRITE_FAILED
146     | VIR_ERR_XML_DETAIL
147     | VIR_ERR_INVALID_NETWORK
148     | VIR_ERR_NETWORK_EXIST
149     | VIR_ERR_SYSTEM_ERROR
150     | VIR_ERR_RPC
151     | VIR_ERR_GNUTLS_ERROR
152     | VIR_WAR_NO_NETWORK
153     | VIR_ERR_NO_DOMAIN
154     | VIR_ERR_NO_NETWORK
155     | VIR_ERR_INVALID_MAC
156     | VIR_ERR_AUTH_FAILED
157     | VIR_ERR_INVALID_STORAGE_POOL
158     | VIR_ERR_INVALID_STORAGE_VOL
159     | VIR_WAR_NO_STORAGE
160     | VIR_ERR_NO_STORAGE_POOL
161     | VIR_ERR_NO_STORAGE_VOL
162     | VIR_ERR_UNKNOWN of int
163
164   let string_of_code = function
165     | VIR_ERR_OK -> "VIR_ERR_OK"
166     | VIR_ERR_INTERNAL_ERROR -> "VIR_ERR_INTERNAL_ERROR"
167     | VIR_ERR_NO_MEMORY -> "VIR_ERR_NO_MEMORY"
168     | VIR_ERR_NO_SUPPORT -> "VIR_ERR_NO_SUPPORT"
169     | VIR_ERR_UNKNOWN_HOST -> "VIR_ERR_UNKNOWN_HOST"
170     | VIR_ERR_NO_CONNECT -> "VIR_ERR_NO_CONNECT"
171     | VIR_ERR_INVALID_CONN -> "VIR_ERR_INVALID_CONN"
172     | VIR_ERR_INVALID_DOMAIN -> "VIR_ERR_INVALID_DOMAIN"
173     | VIR_ERR_INVALID_ARG -> "VIR_ERR_INVALID_ARG"
174     | VIR_ERR_OPERATION_FAILED -> "VIR_ERR_OPERATION_FAILED"
175     | VIR_ERR_GET_FAILED -> "VIR_ERR_GET_FAILED"
176     | VIR_ERR_POST_FAILED -> "VIR_ERR_POST_FAILED"
177     | VIR_ERR_HTTP_ERROR -> "VIR_ERR_HTTP_ERROR"
178     | VIR_ERR_SEXPR_SERIAL -> "VIR_ERR_SEXPR_SERIAL"
179     | VIR_ERR_NO_XEN -> "VIR_ERR_NO_XEN"
180     | VIR_ERR_XEN_CALL -> "VIR_ERR_XEN_CALL"
181     | VIR_ERR_OS_TYPE -> "VIR_ERR_OS_TYPE"
182     | VIR_ERR_NO_KERNEL -> "VIR_ERR_NO_KERNEL"
183     | VIR_ERR_NO_ROOT -> "VIR_ERR_NO_ROOT"
184     | VIR_ERR_NO_SOURCE -> "VIR_ERR_NO_SOURCE"
185     | VIR_ERR_NO_TARGET -> "VIR_ERR_NO_TARGET"
186     | VIR_ERR_NO_NAME -> "VIR_ERR_NO_NAME"
187     | VIR_ERR_NO_OS -> "VIR_ERR_NO_OS"
188     | VIR_ERR_NO_DEVICE -> "VIR_ERR_NO_DEVICE"
189     | VIR_ERR_NO_XENSTORE -> "VIR_ERR_NO_XENSTORE"
190     | VIR_ERR_DRIVER_FULL -> "VIR_ERR_DRIVER_FULL"
191     | VIR_ERR_CALL_FAILED -> "VIR_ERR_CALL_FAILED"
192     | VIR_ERR_XML_ERROR -> "VIR_ERR_XML_ERROR"
193     | VIR_ERR_DOM_EXIST -> "VIR_ERR_DOM_EXIST"
194     | VIR_ERR_OPERATION_DENIED -> "VIR_ERR_OPERATION_DENIED"
195     | VIR_ERR_OPEN_FAILED -> "VIR_ERR_OPEN_FAILED"
196     | VIR_ERR_READ_FAILED -> "VIR_ERR_READ_FAILED"
197     | VIR_ERR_PARSE_FAILED -> "VIR_ERR_PARSE_FAILED"
198     | VIR_ERR_CONF_SYNTAX -> "VIR_ERR_CONF_SYNTAX"
199     | VIR_ERR_WRITE_FAILED -> "VIR_ERR_WRITE_FAILED"
200     | VIR_ERR_XML_DETAIL -> "VIR_ERR_XML_DETAIL"
201     | VIR_ERR_INVALID_NETWORK -> "VIR_ERR_INVALID_NETWORK"
202     | VIR_ERR_NETWORK_EXIST -> "VIR_ERR_NETWORK_EXIST"
203     | VIR_ERR_SYSTEM_ERROR -> "VIR_ERR_SYSTEM_ERROR"
204     | VIR_ERR_RPC -> "VIR_ERR_RPC"
205     | VIR_ERR_GNUTLS_ERROR -> "VIR_ERR_GNUTLS_ERROR"
206     | VIR_WAR_NO_NETWORK -> "VIR_WAR_NO_NETWORK"
207     | VIR_ERR_NO_DOMAIN -> "VIR_ERR_NO_DOMAIN"
208     | VIR_ERR_NO_NETWORK -> "VIR_ERR_NO_NETWORK"
209     | VIR_ERR_INVALID_MAC -> "VIR_ERR_INVALID_MAC"
210     | VIR_ERR_AUTH_FAILED -> "VIR_ERR_AUTH_FAILED"
211     | VIR_ERR_INVALID_STORAGE_POOL -> "VIR_ERR_INVALID_STORAGE_POOL"
212     | VIR_ERR_INVALID_STORAGE_VOL -> "VIR_ERR_INVALID_STORAGE_VOL"
213     | VIR_WAR_NO_STORAGE -> "VIR_WAR_NO_STORAGE"
214     | VIR_ERR_NO_STORAGE_POOL -> "VIR_ERR_NO_STORAGE_POOL"
215     | VIR_ERR_NO_STORAGE_VOL -> "VIR_ERR_NO_STORAGE_VOL"
216     | VIR_ERR_UNKNOWN i -> "VIR_ERR_" ^ string_of_int i
217
218   type domain =
219     | VIR_FROM_NONE
220     | VIR_FROM_XEN
221     | VIR_FROM_XEND
222     | VIR_FROM_XENSTORE
223     | VIR_FROM_SEXPR
224     | VIR_FROM_XML
225     | VIR_FROM_DOM
226     | VIR_FROM_RPC
227     | VIR_FROM_PROXY
228     | VIR_FROM_CONF
229     | VIR_FROM_QEMU
230     | VIR_FROM_NET
231     | VIR_FROM_TEST
232     | VIR_FROM_REMOTE
233     | VIR_FROM_OPENVZ
234     | VIR_FROM_XENXM
235     | VIR_FROM_STATS_LINUX
236     | VIR_FROM_STORAGE
237     | VIR_FROM_UNKNOWN of int
238
239   let string_of_domain = function
240     | VIR_FROM_NONE -> "VIR_FROM_NONE"
241     | VIR_FROM_XEN -> "VIR_FROM_XEN"
242     | VIR_FROM_XEND -> "VIR_FROM_XEND"
243     | VIR_FROM_XENSTORE -> "VIR_FROM_XENSTORE"
244     | VIR_FROM_SEXPR -> "VIR_FROM_SEXPR"
245     | VIR_FROM_XML -> "VIR_FROM_XML"
246     | VIR_FROM_DOM -> "VIR_FROM_DOM"
247     | VIR_FROM_RPC -> "VIR_FROM_RPC"
248     | VIR_FROM_PROXY -> "VIR_FROM_PROXY"
249     | VIR_FROM_CONF -> "VIR_FROM_CONF"
250     | VIR_FROM_QEMU -> "VIR_FROM_QEMU"
251     | VIR_FROM_NET -> "VIR_FROM_NET"
252     | VIR_FROM_TEST -> "VIR_FROM_TEST"
253     | VIR_FROM_REMOTE -> "VIR_FROM_REMOTE"
254     | VIR_FROM_OPENVZ -> "VIR_FROM_OPENVZ"
255     | VIR_FROM_XENXM -> "VIR_FROM_XENXM"
256     | VIR_FROM_STATS_LINUX -> "VIR_FROM_STATS_LINUX"
257     | VIR_FROM_STORAGE -> "VIR_FROM_STORAGE"
258     | VIR_FROM_UNKNOWN i -> "VIR_FROM_" ^ string_of_int i
259
260   type level =
261     | VIR_ERR_NONE
262     | VIR_ERR_WARNING
263     | VIR_ERR_ERROR
264     | VIR_ERR_UNKNOWN_LEVEL of int
265
266   let string_of_level = function
267     | VIR_ERR_NONE -> "VIR_ERR_NONE"
268     | VIR_ERR_WARNING -> "VIR_ERR_WARNING"
269     | VIR_ERR_ERROR -> "VIR_ERR_ERROR"
270     | VIR_ERR_UNKNOWN_LEVEL i -> "VIR_ERR_LEVEL_" ^ string_of_int i
271
272   type t = {
273     code : code;
274     domain : domain;
275     message : string option;
276     level : level;
277     str1 : string option;
278     str2 : string option;
279     str3 : string option;
280     int1 : int32;
281     int2 : int32;
282   }
283
284   let to_string { code = code; domain = domain; message = message } =
285     let buf = Buffer.create 128 in
286     Buffer.add_string buf "libvirt: ";
287     Buffer.add_string buf (string_of_code code);
288     Buffer.add_string buf ": ";
289     Buffer.add_string buf (string_of_domain domain);
290     Buffer.add_string buf ": ";
291     (match message with Some msg -> Buffer.add_string buf msg | None -> ());
292     Buffer.contents buf
293
294   external get_last_error : unit -> t option = "ocaml_libvirt_virterror_get_last_error"
295   external get_last_conn_error : [>`R] Connect.t -> t option = "ocaml_libvirt_virterror_get_last_conn_error"
296   external reset_last_error : unit -> unit = "ocaml_libvirt_virterror_reset_last_error"
297   external reset_last_conn_error : [>`R] Connect.t -> unit = "ocaml_libvirt_virterror_reset_last_conn_error"
298
299   let no_error () =
300     { code = VIR_ERR_OK; domain = VIR_FROM_NONE;
301       message = None; level = VIR_ERR_NONE;
302       str1 = None; str2 = None; str3 = None;
303       int1 = 0_l; int2 = 0_l }
304 end
305
306 exception Virterror of Virterror.t
307 exception Not_supported of string
308
309 let rec map_ignore_errors f = function
310   | [] -> []
311   | x :: xs ->
312       try f x :: map_ignore_errors f xs
313       with Virterror _ -> map_ignore_errors f xs
314
315 module Domain =
316 struct
317   type 'rw t
318
319   type state =
320     | InfoNoState | InfoRunning | InfoBlocked | InfoPaused
321     | InfoShutdown | InfoShutoff | InfoCrashed
322
323   type info = {
324     state : state;
325     max_mem : int64;
326     memory : int64;
327     nr_virt_cpu : int;
328     cpu_time : int64;
329   }
330
331   type vcpu_state = VcpuOffline | VcpuRunning | VcpuBlocked
332
333   type vcpu_info = {
334     number : int;
335     vcpu_state : vcpu_state;
336     vcpu_time : int64;
337     cpu : int;
338   }
339
340   type sched_param = string * sched_param_value
341   and sched_param_value =
342     | SchedFieldInt32 of int32 | SchedFieldUInt32 of int32
343     | SchedFieldInt64 of int64 | SchedFieldUInt64 of int64
344     | SchedFieldFloat of float | SchedFieldBool of bool
345
346   type migrate_flag = Live
347
348   type memory_flag = Virtual
349
350   type list_flag =
351     | ListActive
352     | ListInactive
353     | ListAll
354
355   type block_stats = {
356     rd_req : int64;
357     rd_bytes : int64;
358     wr_req : int64;
359     wr_bytes : int64;
360     errs : int64;
361   }
362
363   type interface_stats = {
364     rx_bytes : int64;
365     rx_packets : int64;
366     rx_errs : int64;
367     rx_drop : int64;
368     tx_bytes : int64;
369     tx_packets : int64;
370     tx_errs : int64;
371     tx_drop : int64;
372   }
373
374   (* The maximum size for Domain.memory_peek and Domain.block_peek
375    * supported by libvirt.  This may change with different versions
376    * of libvirt in the future, hence it's a function.
377    *)
378   let max_peek _ = 65536
379
380   external list_all_domains : 'a Connect.t -> ?want_info:bool -> list_flag list -> 'a t array * info array = "ocaml_libvirt_connect_list_all_domains"
381
382   external create_linux : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_domain_create_linux"
383   external create_linux_job : [>`W] Connect.t -> xml -> ([`Domain], rw) job_t = "ocaml_libvirt_domain_create_linux_job"
384   external lookup_by_id : 'a Connect.t -> int -> 'a t = "ocaml_libvirt_domain_lookup_by_id"
385   external lookup_by_uuid : 'a Connect.t -> uuid -> 'a t = "ocaml_libvirt_domain_lookup_by_uuid"
386   external lookup_by_uuid_string : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_domain_lookup_by_uuid_string"
387   external lookup_by_name : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_domain_lookup_by_name"
388   external destroy : [>`W] t -> unit = "ocaml_libvirt_domain_destroy"
389   external free : [>`R] t -> unit = "ocaml_libvirt_domain_free"
390   external suspend : [>`W] t -> unit = "ocaml_libvirt_domain_suspend"
391   external resume : [>`W] t -> unit = "ocaml_libvirt_domain_resume"
392   external save : [>`W] t -> filename -> unit = "ocaml_libvirt_domain_save"
393   external save_job : [>`W] t -> filename -> ([`Domain_nocreate], rw) job_t = "ocaml_libvirt_domain_save_job"
394   external restore : [>`W] Connect.t -> filename -> unit = "ocaml_libvirt_domain_restore"
395   external restore_job : [>`W] Connect.t -> filename -> ([`Domain_nocreate], rw) job_t = "ocaml_libvirt_domain_restore_job"
396   external core_dump : [>`W] t -> filename -> unit = "ocaml_libvirt_domain_core_dump"
397   external core_dump_job : [>`W] t -> filename -> ([`Domain_nocreate], rw) job_t = "ocaml_libvirt_domain_core_dump_job"
398   external shutdown : [>`W] t -> unit = "ocaml_libvirt_domain_shutdown"
399   external reboot : [>`W] t -> unit = "ocaml_libvirt_domain_reboot"
400   external get_name : [>`R] t -> string = "ocaml_libvirt_domain_get_name"
401   external get_uuid : [>`R] t -> uuid = "ocaml_libvirt_domain_get_uuid"
402   external get_uuid_string : [>`R] t -> string = "ocaml_libvirt_domain_get_uuid_string"
403   external get_id : [>`R] t -> int = "ocaml_libvirt_domain_get_id"
404   external get_os_type : [>`R] t -> string = "ocaml_libvirt_domain_get_os_type"
405   external get_max_memory : [>`R] t -> int64 = "ocaml_libvirt_domain_get_max_memory"
406   external set_max_memory : [>`W] t -> int64 -> unit = "ocaml_libvirt_domain_set_max_memory"
407   external set_memory : [>`W] t -> int64 -> unit = "ocaml_libvirt_domain_set_memory"
408   external get_info : [>`R] t -> info = "ocaml_libvirt_domain_get_info"
409   external get_xml_desc : [>`R] t -> xml = "ocaml_libvirt_domain_get_xml_desc"
410   external get_scheduler_type : [>`R] t -> string * int = "ocaml_libvirt_domain_get_scheduler_type"
411   external get_scheduler_parameters : [>`R] t -> int -> sched_param array = "ocaml_libvirt_domain_get_scheduler_parameters"
412   external set_scheduler_parameters : [>`W] t -> sched_param array -> unit = "ocaml_libvirt_domain_set_scheduler_parameters"
413   external define_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_domain_define_xml"
414   external undefine : [>`W] t -> unit = "ocaml_libvirt_domain_undefine"
415   external create : [>`W] t -> unit = "ocaml_libvirt_domain_create"
416   external create_job : [>`W] t -> ([`Domain_nocreate], rw) job_t = "ocaml_libvirt_domain_create_job"
417   external get_autostart : [>`R] t -> bool = "ocaml_libvirt_domain_get_autostart"
418   external set_autostart : [>`W] t -> bool -> unit = "ocaml_libvirt_domain_set_autostart"
419   external set_vcpus : [>`W] t -> int -> unit = "ocaml_libvirt_domain_set_vcpus"
420   external pin_vcpu : [>`W] t -> int -> string -> unit = "ocaml_libvirt_domain_pin_vcpu"
421   external get_vcpus : [>`R] t -> int -> int -> int * vcpu_info array * string = "ocaml_libvirt_domain_get_vcpus"
422   external get_max_vcpus : [>`R] t -> int = "ocaml_libvirt_domain_get_max_vcpus"
423   external attach_device : [>`W] t -> xml -> unit = "ocaml_libvirt_domain_attach_device"
424   external detach_device : [>`W] t -> xml -> unit = "ocaml_libvirt_domain_detach_device"
425   external migrate : [>`W] t -> [>`W] Connect.t -> migrate_flag list -> ?dname:string -> ?uri:string -> ?bandwidth:int -> unit -> rw t = "ocaml_libvirt_domain_migrate_bytecode" "ocaml_libvirt_domain_migrate_native"
426   external block_stats : [>`R] t -> string -> block_stats = "ocaml_libvirt_domain_block_stats"
427   external interface_stats : [>`R] t -> string -> interface_stats = "ocaml_libvirt_domain_interface_stats"
428   external block_peek : [>`R] t -> string -> int64 -> int -> string -> int -> unit = "ocaml_libvirt_domain_block_peek_bytecode" "ocaml_libvirt_domain_block_peek_native"
429   external memory_peek : [>`R] t -> memory_flag list -> int64 -> int -> string -> int -> unit = "ocaml_libvirt_domain_memory_peek_bytecode" "ocaml_libvirt_domain_memory_peek_native"
430
431   external const : [>`R] t -> ro t = "%identity"
432
433   (* First time we are called, we will check if
434    * virConnectListAllDomains is supported.
435    *)
436   let have_list_all_domains = ref None
437
438   let check_have_list_all_domains conn =
439     match !have_list_all_domains with
440     | Some v -> v
441     | None ->
442         (* Check if virConnectListAllDomains is supported
443          * by this version of libvirt.
444          *)
445         let v =
446           (* libvirt has a short-cut which makes this very quick ... *)
447           try ignore (list_all_domains conn []); true
448           with Not_supported "virConnectListAllDomains" -> false in
449         have_list_all_domains := Some v;
450         v
451
452   let get_domains conn flags =
453     let have_list_all_domains = check_have_list_all_domains conn in
454
455     if have_list_all_domains then (
456       (* Good, we can use the shiny new method. *)
457       let doms, _ = list_all_domains conn ~want_info:false flags in
458       Array.to_list doms
459     )
460     else (
461       (* Old/slow/inefficient method. *)
462       let get_active, get_inactive =
463         if List.mem ListAll flags then
464           (true, true)
465         else
466           (List.mem ListActive flags, List.mem ListInactive flags) in
467       let active_doms =
468         if get_active then (
469           let n = Connect.num_of_domains conn in
470           let ids = Connect.list_domains conn n in
471           let ids = Array.to_list ids in
472           map_ignore_errors (lookup_by_id conn) ids
473         ) else [] in
474
475       let inactive_doms =
476         if get_inactive then (
477           let n = Connect.num_of_defined_domains conn in
478           let names = Connect.list_defined_domains conn n in
479           let names = Array.to_list names in
480           map_ignore_errors (lookup_by_name conn) names
481         ) else [] in
482
483       active_doms @ inactive_doms
484     )
485
486   let get_domains_and_infos conn flags =
487     let have_list_all_domains = check_have_list_all_domains conn in
488
489     if have_list_all_domains then (
490       (* Good, we can use the shiny new method. *)
491       let doms, infos = list_all_domains conn ~want_info:true flags in
492       let doms = Array.to_list doms and infos = Array.to_list infos in
493       List.combine doms infos
494     )
495     else (
496       (* Old/slow/inefficient method. *)
497       let get_active, get_inactive =
498         if List.mem ListAll flags then
499           (true, true)
500         else (List.mem ListActive flags, List.mem ListInactive flags) in
501       let active_doms =
502         if get_active then (
503           let n = Connect.num_of_domains conn in
504           let ids = Connect.list_domains conn n in
505           let ids = Array.to_list ids in
506           map_ignore_errors (lookup_by_id conn) ids
507         ) else [] in
508
509       let inactive_doms =
510         if get_inactive then (
511           let n = Connect.num_of_defined_domains conn in
512           let names = Connect.list_defined_domains conn n in
513           let names = Array.to_list names in
514           map_ignore_errors (lookup_by_name conn) names
515         ) else [] in
516
517       let doms = active_doms @ inactive_doms in
518
519       map_ignore_errors (fun dom -> (dom, get_info dom)) doms
520     )
521 end
522
523 module Network =
524 struct
525   type 'rw t
526
527   external lookup_by_name : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_network_lookup_by_name"
528   external lookup_by_uuid : 'a Connect.t -> uuid -> 'a t = "ocaml_libvirt_network_lookup_by_uuid"
529   external lookup_by_uuid_string : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_network_lookup_by_uuid_string"
530   external create_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_network_create_xml"
531   external create_xml_job : [>`W] Connect.t -> xml -> ([`Network], rw) job_t = "ocaml_libvirt_network_create_xml_job"
532   external define_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_network_define_xml"
533   external undefine : [>`W] t -> unit = "ocaml_libvirt_network_undefine"
534   external create : [>`W] t -> unit = "ocaml_libvirt_network_create"
535   external create_job : [>`W] t -> ([`Network_nocreate], rw) job_t = "ocaml_libvirt_network_create_job"
536   external destroy : [>`W] t -> unit = "ocaml_libvirt_network_destroy"
537   external free : [>`R] t -> unit = "ocaml_libvirt_network_free"
538   external get_name : [>`R] t -> string = "ocaml_libvirt_network_get_name"
539   external get_uuid : [>`R] t -> uuid = "ocaml_libvirt_network_get_uuid"
540   external get_uuid_string : [>`R] t -> string = "ocaml_libvirt_network_get_uuid_string"
541   external get_xml_desc : [>`R] t -> xml = "ocaml_libvirt_network_get_xml_desc"
542   external get_bridge_name : [>`R] t -> string = "ocaml_libvirt_network_get_bridge_name"
543   external get_autostart : [>`R] t -> bool = "ocaml_libvirt_network_get_autostart"
544   external set_autostart : [>`W] t -> bool -> unit = "ocaml_libvirt_network_set_autostart"
545
546   external const : [>`R] t -> ro t = "%identity"
547 end
548
549 module Pool =
550 struct
551   type 'rw t
552   type pool_state = Inactive | Building | Running | Degraded
553   type pool_build_flags = New | Repair | Resize
554   type pool_delete_flags = Normal | Zeroed
555   type pool_info = {
556     state : pool_state;
557     capacity : int64;
558     allocation : int64;
559     available : int64;
560   }
561
562   external lookup_by_name : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_pool_lookup_by_name"
563   external lookup_by_uuid : 'a Connect.t -> uuid -> 'a t = "ocaml_libvirt_storage_pool_lookup_by_uuid"
564   external lookup_by_uuid_string : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_pool_lookup_by_uuid_string"
565   external create_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_storage_pool_create_xml"
566   external define_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_storage_pool_define_xml"
567   external build : [>`W] t -> pool_build_flags -> unit = "ocaml_libvirt_storage_pool_build"
568   external undefine : [>`W] t -> unit = "ocaml_libvirt_storage_pool_undefine"
569   external create : [>`W] t -> unit = "ocaml_libvirt_storage_pool_create"
570   external destroy : [>`W] t -> unit = "ocaml_libvirt_storage_pool_destroy"
571   external delete : [>`W] t -> unit = "ocaml_libvirt_storage_pool_delete"
572   external free : [>`R] t -> unit = "ocaml_libvirt_storage_pool_free"
573   external refresh : [`R] t -> unit = "ocaml_libvirt_storage_pool_refresh"
574   external get_name : [`R] t -> string = "ocaml_libvirt_storage_pool_get_name"
575   external get_uuid : [`R] t -> uuid = "ocaml_libvirt_storage_pool_get_uuid"
576   external get_uuid_string : [`R] t -> string = "ocaml_libvirt_storage_pool_get_uuid_string"
577   external get_info : [`R] t -> pool_info = "ocaml_libvirt_storage_pool_get_info"
578   external get_xml_desc : [`R] t -> xml = "ocaml_libvirt_storage_pool_get_xml_desc"
579   external get_autostart : [`R] t -> bool = "ocaml_libvirt_storage_pool_get_autostart"
580   external set_autostart : [`W] t -> bool -> unit = "ocaml_libvirt_storage_pool_set_autostart"
581   external num_of_volumes : [`R] t -> int = "ocaml_libvirt_storage_pool_num_of_volumes"
582   external list_volumes : [`R] t -> int -> string array = "ocaml_libvirt_storage_pool_list_volumes"
583   external const : [>`R] t -> ro t = "%identity"
584 end
585
586 module Volume =
587 struct
588   type 'rw t
589   type vol_type = File | Block
590   type vol_delete_flags = Normal | Zeroed
591   type vol_info = {
592     typ : vol_type;
593     capacity : int64;
594     allocation : int64;
595   }
596
597   external lookup_by_name : 'a Pool.t -> string -> 'a t = "ocaml_libvirt_storage_vol_lookup_by_name"
598   external lookup_by_key : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_vol_lookup_by_key"
599   external lookup_by_path : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_vol_lookup_by_path"
600   external pool_of_volume : 'a t -> 'a Pool.t = "ocaml_libvirt_storage_pool_lookup_by_volume"
601   external get_name : [`R] t -> string = "ocaml_libvirt_storage_vol_get_name"
602   external get_key : [`R] t -> string = "ocaml_libvirt_storage_vol_get_key"
603   external get_path : [`R] t -> string = "ocaml_libvirt_storage_vol_get_path"
604   external get_info : [`R] t -> vol_info = "ocaml_libvirt_storage_vol_get_info"
605   external get_xml_desc : [`R] t -> xml = "ocaml_libvirt_storage_vol_get_xml_desc"
606   external create_xml : [`W] Pool.t -> xml -> unit = "ocaml_libvirt_storage_vol_create_xml"
607   external delete : [`W] t -> unit = "ocaml_libvirt_storage_vol_delete"
608   external free : [>`R] t -> unit = "ocaml_libvirt_storage_vol_free"
609   external const : [>`R] t -> ro t = "%identity"
610 end
611
612 module Job =
613 struct
614   type ('jobclass, 'rw) t = ('jobclass, 'rw) job_t
615   type job_type = Bounded | Unbounded
616   type job_state = Running | Complete | Failed | Cancelled
617   type job_info = {
618     typ : job_type;
619     state : job_state;
620     running_time : int;
621     remaining_time : int;
622     percent_complete : int
623   }
624   external get_info : ('a,'b) t -> job_info = "ocaml_libvirt_job_get_info"
625   external get_domain : ([`Domain], 'a) t -> 'a Domain.t = "ocaml_libvirt_job_get_domain"
626   external get_network : ([`Network], 'a) t -> 'a Network.t = "ocaml_libvirt_job_get_network"
627   external cancel : ('a,'b) t -> unit = "ocaml_libvirt_job_cancel"
628   external free : ('a, [>`R]) t -> unit = "ocaml_libvirt_job_free"
629   external const : ('a, [>`R]) t -> ('a, ro) t = "%identity"
630 end
631
632 (* Initialization. *)
633 external c_init : unit -> unit = "ocaml_libvirt_init"
634 let () =
635   Callback.register_exception
636     "ocaml_libvirt_virterror" (Virterror (Virterror.no_error ()));
637   Callback.register_exception
638     "ocaml_libvirt_not_supported" (Not_supported "");
639   c_init ()