Add a binding for virConnectGetAllDomainStats (RHBZ#1390171).
[ocaml-libvirt.git] / libvirt / libvirt.ml
1 (* OCaml bindings for libvirt.
2    (C) Copyright 2007-2015 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 module Connect =
37 struct
38   type 'rw t
39
40   type node_info = {
41     model : string;
42     memory : int64;
43     cpus : int;
44     mhz : int;
45     nodes : int;
46     sockets : int;
47     cores : int;
48     threads : int;
49   }
50
51   type list_flag =
52     | ListNoState | ListRunning | ListBlocked
53     | ListPaused | ListShutdown | ListShutoff | ListCrashed
54     | ListActive
55     | ListInactive
56     | ListAll
57
58   external connect : ?name:string -> unit -> rw t = "ocaml_libvirt_connect_open"
59   external connect_readonly : ?name:string -> unit -> ro t = "ocaml_libvirt_connect_open_readonly"
60   external close : [>`R] t -> unit = "ocaml_libvirt_connect_close"
61   external get_type : [>`R] t -> string = "ocaml_libvirt_connect_get_type"
62   external get_version : [>`R] t -> int = "ocaml_libvirt_connect_get_version"
63   external get_hostname : [>`R] t -> string = "ocaml_libvirt_connect_get_hostname"
64   external get_uri : [>`R] t -> string = "ocaml_libvirt_connect_get_uri"
65   external get_max_vcpus : [>`R] t -> ?type_:string -> unit -> int = "ocaml_libvirt_connect_get_max_vcpus"
66   external list_domains : [>`R] t -> int -> int array = "ocaml_libvirt_connect_list_domains"
67   external num_of_domains : [>`R] t -> int = "ocaml_libvirt_connect_num_of_domains"
68   external get_capabilities : [>`R] t -> xml = "ocaml_libvirt_connect_get_capabilities"
69   external num_of_defined_domains : [>`R] t -> int = "ocaml_libvirt_connect_num_of_defined_domains"
70   external list_defined_domains : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_defined_domains"
71   external num_of_networks : [>`R] t -> int = "ocaml_libvirt_connect_num_of_networks"
72   external list_networks : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_networks"
73   external num_of_defined_networks : [>`R] t -> int = "ocaml_libvirt_connect_num_of_defined_networks"
74   external list_defined_networks : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_defined_networks"
75   external num_of_pools : [>`R] t -> int = "ocaml_libvirt_connect_num_of_storage_pools"
76   external list_pools : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_storage_pools"
77   external num_of_defined_pools : [>`R] t -> int = "ocaml_libvirt_connect_num_of_defined_storage_pools"
78   external list_defined_pools : [>`R] t -> int -> string array = "ocaml_libvirt_connect_list_defined_storage_pools"
79
80   external get_node_info : [>`R] t -> node_info = "ocaml_libvirt_connect_get_node_info"
81   external node_get_free_memory : [> `R] t -> int64 = "ocaml_libvirt_connect_node_get_free_memory"
82   external node_get_cells_free_memory : [> `R] t -> int -> int -> int64 array = "ocaml_libvirt_connect_node_get_cells_free_memory"
83
84   (* See VIR_NODEINFO_MAXCPUS macro defined in <libvirt.h>. *)
85   let maxcpus_of_node_info { nodes = nodes; sockets = sockets;
86                              cores = cores; threads = threads } =
87     nodes * sockets * cores * threads
88
89   (* See VIR_CPU_MAPLEN macro defined in <libvirt.h>. *)
90   let cpumaplen nr_cpus =
91     (nr_cpus + 7) / 8
92
93   (* See VIR_USE_CPU, VIR_UNUSE_CPU, VIR_CPU_USABLE macros defined in <libvirt.h>. *)
94   let use_cpu cpumap cpu =
95     cpumap.[cpu/8] <-
96       Char.chr (Char.code cpumap.[cpu/8] lor (1 lsl (cpu mod 8)))
97   let unuse_cpu cpumap cpu =
98     cpumap.[cpu/8] <-
99       Char.chr (Char.code cpumap.[cpu/8] land (lnot (1 lsl (cpu mod 8))))
100   let cpu_usable cpumaps maplen vcpu cpu =
101     Char.code cpumaps.[vcpu*maplen + cpu/8] land (1 lsl (cpu mod 8)) <> 0
102
103   external set_keep_alive : [>`R] t -> int -> int -> unit = "ocaml_libvirt_connect_set_keep_alive"
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 domain_create_flag =
341   | START_PAUSED
342   | START_AUTODESTROY
343   | START_BYPASS_CACHE
344   | START_FORCE_BOOT
345   | START_VALIDATE
346   let rec int_of_domain_create_flags = function
347     | [] -> 0
348     | START_PAUSED :: flags ->       1 lor int_of_domain_create_flags flags
349     | START_AUTODESTROY :: flags ->  2 lor int_of_domain_create_flags flags
350     | START_BYPASS_CACHE :: flags -> 4 lor int_of_domain_create_flags flags
351     | START_FORCE_BOOT :: flags ->   8 lor int_of_domain_create_flags flags
352     | START_VALIDATE :: flags ->    16 lor int_of_domain_create_flags flags
353
354   type sched_param = string * sched_param_value
355   and sched_param_value =
356     | SchedFieldInt32 of int32 | SchedFieldUInt32 of int32
357     | SchedFieldInt64 of int64 | SchedFieldUInt64 of int64
358     | SchedFieldFloat of float | SchedFieldBool of bool
359
360   type typed_param = string * typed_param_value
361   and typed_param_value =
362     | TypedFieldInt32 of int32 | TypedFieldUInt32 of int32
363     | TypedFieldInt64 of int64 | TypedFieldUInt64 of int64
364     | TypedFieldFloat of float | TypedFieldBool of bool
365     | TypedFieldString of string
366
367   type migrate_flag = Live
368
369   type memory_flag = Virtual
370
371   type list_flag =
372     | ListActive
373     | ListInactive
374     | ListAll
375
376   type block_stats = {
377     rd_req : int64;
378     rd_bytes : int64;
379     wr_req : int64;
380     wr_bytes : int64;
381     errs : int64;
382   }
383
384   type interface_stats = {
385     rx_bytes : int64;
386     rx_packets : int64;
387     rx_errs : int64;
388     rx_drop : int64;
389     tx_bytes : int64;
390     tx_packets : int64;
391     tx_errs : int64;
392     tx_drop : int64;
393   }
394
395   type get_all_domain_stats_flag =
396     | GetAllDomainsStatsActive
397     | GetAllDomainsStatsInactive
398     | GetAllDomainsStatsOther
399     | GetAllDomainsStatsPaused
400     | GetAllDomainsStatsPersistent
401     | GetAllDomainsStatsRunning
402     | GetAllDomainsStatsShutoff
403     | GetAllDomainsStatsTransient
404     | GetAllDomainsStatsBacking
405     | GetAllDomainsStatsEnforceStats
406
407   type stats_type =
408     | StatsState | StatsCpuTotal | StatsBalloon | StatsVcpu
409     | StatsInterface | StatsBlock | StatsPerf
410
411   type 'a domain_stats_record = {
412     dom : 'a t;
413     params : typed_param array;
414   }
415
416   (* The maximum size for Domain.memory_peek and Domain.block_peek
417    * supported by libvirt.  This may change with different versions
418    * of libvirt in the future, hence it's a function.
419    *)
420   let max_peek _ = 65536
421
422   external create_linux : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_domain_create_linux"
423   external _create_xml : [>`W] Connect.t -> xml -> int -> rw t = "ocaml_libvirt_domain_create_xml"
424   let create_xml conn xml flags =
425     _create_xml conn xml (int_of_domain_create_flags flags)
426   external lookup_by_id : 'a Connect.t -> int -> 'a t = "ocaml_libvirt_domain_lookup_by_id"
427   external lookup_by_uuid : 'a Connect.t -> uuid -> 'a t = "ocaml_libvirt_domain_lookup_by_uuid"
428   external lookup_by_uuid_string : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_domain_lookup_by_uuid_string"
429   external lookup_by_name : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_domain_lookup_by_name"
430   external destroy : [>`W] t -> unit = "ocaml_libvirt_domain_destroy"
431   external free : [>`R] t -> unit = "ocaml_libvirt_domain_free"
432   external suspend : [>`W] t -> unit = "ocaml_libvirt_domain_suspend"
433   external resume : [>`W] t -> unit = "ocaml_libvirt_domain_resume"
434   external save : [>`W] t -> filename -> unit = "ocaml_libvirt_domain_save"
435   external restore : [>`W] Connect.t -> filename -> unit = "ocaml_libvirt_domain_restore"
436   external core_dump : [>`W] t -> filename -> unit = "ocaml_libvirt_domain_core_dump"
437   external shutdown : [>`W] t -> unit = "ocaml_libvirt_domain_shutdown"
438   external reboot : [>`W] t -> unit = "ocaml_libvirt_domain_reboot"
439   external get_name : [>`R] t -> string = "ocaml_libvirt_domain_get_name"
440   external get_uuid : [>`R] t -> uuid = "ocaml_libvirt_domain_get_uuid"
441   external get_uuid_string : [>`R] t -> string = "ocaml_libvirt_domain_get_uuid_string"
442   external get_id : [>`R] t -> int = "ocaml_libvirt_domain_get_id"
443   external get_os_type : [>`R] t -> string = "ocaml_libvirt_domain_get_os_type"
444   external get_max_memory : [>`R] t -> int64 = "ocaml_libvirt_domain_get_max_memory"
445   external set_max_memory : [>`W] t -> int64 -> unit = "ocaml_libvirt_domain_set_max_memory"
446   external set_memory : [>`W] t -> int64 -> unit = "ocaml_libvirt_domain_set_memory"
447   external get_info : [>`R] t -> info = "ocaml_libvirt_domain_get_info"
448   external get_xml_desc : [>`R] t -> xml = "ocaml_libvirt_domain_get_xml_desc"
449   external get_scheduler_type : [>`R] t -> string * int = "ocaml_libvirt_domain_get_scheduler_type"
450   external get_scheduler_parameters : [>`R] t -> int -> sched_param array = "ocaml_libvirt_domain_get_scheduler_parameters"
451   external set_scheduler_parameters : [>`W] t -> sched_param array -> unit = "ocaml_libvirt_domain_set_scheduler_parameters"
452   external define_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_domain_define_xml"
453   external undefine : [>`W] t -> unit = "ocaml_libvirt_domain_undefine"
454   external create : [>`W] t -> unit = "ocaml_libvirt_domain_create"
455   external get_autostart : [>`R] t -> bool = "ocaml_libvirt_domain_get_autostart"
456   external set_autostart : [>`W] t -> bool -> unit = "ocaml_libvirt_domain_set_autostart"
457   external set_vcpus : [>`W] t -> int -> unit = "ocaml_libvirt_domain_set_vcpus"
458   external pin_vcpu : [>`W] t -> int -> string -> unit = "ocaml_libvirt_domain_pin_vcpu"
459   external get_vcpus : [>`R] t -> int -> int -> int * vcpu_info array * string = "ocaml_libvirt_domain_get_vcpus"
460   external get_cpu_stats : [>`R] t -> typed_param list array = "ocaml_libvirt_domain_get_cpu_stats"
461   external get_max_vcpus : [>`R] t -> int = "ocaml_libvirt_domain_get_max_vcpus"
462   external attach_device : [>`W] t -> xml -> unit = "ocaml_libvirt_domain_attach_device"
463   external detach_device : [>`W] t -> xml -> unit = "ocaml_libvirt_domain_detach_device"
464   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"
465   external block_stats : [>`R] t -> string -> block_stats = "ocaml_libvirt_domain_block_stats"
466   external interface_stats : [>`R] t -> string -> interface_stats = "ocaml_libvirt_domain_interface_stats"
467   external block_peek : [>`W] t -> string -> int64 -> int -> string -> int -> unit = "ocaml_libvirt_domain_block_peek_bytecode" "ocaml_libvirt_domain_block_peek_native"
468   external memory_peek : [>`W] t -> memory_flag list -> int64 -> int -> string -> int -> unit = "ocaml_libvirt_domain_memory_peek_bytecode" "ocaml_libvirt_domain_memory_peek_native"
469
470   external get_all_domain_stats : 'a Connect.t -> stats_type list -> get_all_domain_stats_flag list -> 'a domain_stats_record array = "ocaml_libvirt_domain_get_all_domain_stats"
471
472   external const : [>`R] t -> ro t = "%identity"
473
474   let get_domains conn flags =
475     (* Old/slow/inefficient method. *)
476     let get_active, get_inactive =
477       if List.mem ListAll flags then
478         (true, true)
479       else
480         (List.mem ListActive flags, List.mem ListInactive flags) in
481     let active_doms =
482       if get_active then (
483         let n = Connect.num_of_domains conn in
484         let ids = Connect.list_domains conn n in
485         let ids = Array.to_list ids in
486         map_ignore_errors (lookup_by_id conn) ids
487       ) else [] in
488
489     let inactive_doms =
490       if get_inactive then (
491         let n = Connect.num_of_defined_domains conn in
492         let names = Connect.list_defined_domains conn n in
493         let names = Array.to_list names in
494         map_ignore_errors (lookup_by_name conn) names
495       ) else [] in
496
497     active_doms @ inactive_doms
498
499   let get_domains_and_infos conn flags =
500     (* Old/slow/inefficient method. *)
501     let get_active, get_inactive =
502       if List.mem ListAll flags then
503         (true, true)
504       else (List.mem ListActive flags, List.mem ListInactive flags) in
505     let active_doms =
506       if get_active then (
507         let n = Connect.num_of_domains conn in
508         let ids = Connect.list_domains conn n in
509         let ids = Array.to_list ids in
510         map_ignore_errors (lookup_by_id conn) ids
511       ) else [] in
512
513     let inactive_doms =
514       if get_inactive then (
515         let n = Connect.num_of_defined_domains conn in
516         let names = Connect.list_defined_domains conn n in
517         let names = Array.to_list names in
518         map_ignore_errors (lookup_by_name conn) names
519       ) else [] in
520
521     let doms = active_doms @ inactive_doms in
522
523     map_ignore_errors (fun dom -> (dom, get_info dom)) doms
524 end
525
526 module Event =
527 struct
528
529   module Defined = struct
530     type t = [
531       | `Added
532       | `Updated
533       | `Unknown of int
534     ]
535
536     let to_string = function
537       | `Added -> "Added"
538       | `Updated -> "Updated"
539       | `Unknown x -> Printf.sprintf "Unknown Defined.detail: %d" x
540
541     let make = function
542       | 0 -> `Added
543       | 1 -> `Updated
544       | x -> `Unknown x (* newer libvirt *)
545   end
546
547   module Undefined = struct
548     type t = [
549       | `Removed
550       | `Unknown of int
551     ]
552
553     let to_string = function
554       | `Removed -> "UndefinedRemoved"
555       | `Unknown x -> Printf.sprintf "Unknown Undefined.detail: %d" x
556
557     let make = function
558       | 0 -> `Removed
559       | x -> `Unknown x (* newer libvirt *)
560   end
561
562   module Started = struct
563     type t = [
564       | `Booted
565       | `Migrated
566       | `Restored
567       | `FromSnapshot
568       | `Wakeup
569       | `Unknown of int
570     ]
571
572     let to_string = function
573       | `Booted -> "Booted"
574       | `Migrated -> "Migrated"
575       | `Restored -> "Restored"
576       | `FromSnapshot -> "FromSnapshot"
577       | `Wakeup -> "Wakeup"
578       | `Unknown x -> Printf.sprintf "Unknown Started.detail: %d" x
579  
580     let make = function
581       | 0 -> `Booted
582       | 1 -> `Migrated
583       | 2 -> `Restored
584       | 3 -> `FromSnapshot
585       | 4 -> `Wakeup
586       | x -> `Unknown x (* newer libvirt *)
587   end
588
589   module Suspended = struct
590     type t = [
591       | `Paused
592       | `Migrated
593       | `IOError
594       | `Watchdog
595       | `Restored
596       | `FromSnapshot
597       | `APIError
598       | `Unknown of int (* newer libvirt *)
599     ]
600
601     let to_string = function
602       | `Paused -> "Paused"
603       | `Migrated -> "Migrated"
604       | `IOError -> "IOError"
605       | `Watchdog -> "Watchdog"
606       | `Restored -> "Restored"
607       | `FromSnapshot -> "FromSnapshot"
608       | `APIError -> "APIError"
609       | `Unknown x -> Printf.sprintf "Unknown Suspended.detail: %d" x
610
611      let make = function
612       | 0 -> `Paused
613       | 1 -> `Migrated
614       | 2 -> `IOError
615       | 3 -> `Watchdog
616       | 4 -> `Restored
617       | 5 -> `FromSnapshot
618       | 6 -> `APIError
619       | x -> `Unknown x (* newer libvirt *)
620   end
621
622   module Resumed = struct
623     type t = [
624       | `Unpaused
625       | `Migrated
626       | `FromSnapshot
627       | `Unknown of int (* newer libvirt *)
628     ]
629
630     let to_string = function
631       | `Unpaused -> "Unpaused"
632       | `Migrated -> "Migrated"
633       | `FromSnapshot -> "FromSnapshot"
634       | `Unknown x -> Printf.sprintf "Unknown Resumed.detail: %d" x
635
636     let make = function
637       | 0 -> `Unpaused
638       | 1 -> `Migrated
639       | 2 -> `FromSnapshot
640       | x -> `Unknown x (* newer libvirt *)
641   end
642
643   module Stopped = struct
644     type t = [
645       | `Shutdown
646       | `Destroyed
647       | `Crashed
648       | `Migrated
649       | `Saved
650       | `Failed
651       | `FromSnapshot
652       | `Unknown of int
653     ]
654     let to_string = function
655       | `Shutdown -> "Shutdown"
656       | `Destroyed -> "Destroyed"
657       | `Crashed -> "Crashed"
658       | `Migrated -> "Migrated"
659       | `Saved -> "Saved"
660       | `Failed -> "Failed"
661       | `FromSnapshot -> "FromSnapshot"
662       | `Unknown x -> Printf.sprintf "Unknown Stopped.detail: %d" x
663
664     let make = function
665       | 0 -> `Shutdown
666       | 1 -> `Destroyed
667       | 2 -> `Crashed
668       | 3 -> `Migrated
669       | 4 -> `Saved
670       | 5 -> `Failed
671       | 6 -> `FromSnapshot
672       | x -> `Unknown x (* newer libvirt *)
673   end
674
675   module PM_suspended = struct
676     type t = [
677       | `Memory
678       | `Disk
679       | `Unknown of int (* newer libvirt *)
680     ]
681
682     let to_string = function
683       | `Memory -> "Memory"
684       | `Disk -> "Disk"
685       | `Unknown x -> Printf.sprintf "Unknown PM_suspended.detail: %d" x
686
687     let make = function
688       | 0 -> `Memory
689       | 1 -> `Disk
690       | x -> `Unknown x (* newer libvirt *)
691   end
692
693   let string_option x = match x with
694     | None -> "None"
695     | Some x' -> "Some " ^ x'
696
697   module Lifecycle = struct
698     type t = [
699       | `Defined of Defined.t
700       | `Undefined of Undefined.t
701       | `Started of Started.t
702       | `Suspended of Suspended.t
703       | `Resumed of Resumed.t
704       | `Stopped of Stopped.t
705       | `Shutdown (* no detail defined yet *)
706       | `PMSuspended of PM_suspended.t
707       | `Unknown of int (* newer libvirt *)
708     ]
709
710     let to_string = function
711       | `Defined x -> "Defined " ^ (Defined.to_string x)
712       | `Undefined x -> "Undefined " ^ (Undefined.to_string x)
713       | `Started x -> "Started " ^ (Started.to_string x)
714       | `Suspended x -> "Suspended " ^ (Suspended.to_string x)
715       | `Resumed x -> "Resumed " ^ (Resumed.to_string x)
716       | `Stopped x -> "Stopped " ^ (Stopped.to_string x)
717       | `Shutdown -> "Shutdown"
718       | `PMSuspended x -> "PMSuspended " ^ (PM_suspended.to_string x)
719       | `Unknown x -> Printf.sprintf "Unknown Lifecycle event: %d" x
720
721     let make (ty, detail) = match ty with
722       | 0 -> `Defined (Defined.make detail)
723       | 1 -> `Undefined (Undefined.make detail)
724       | 2 -> `Started (Started.make detail)
725       | 3 -> `Suspended (Suspended.make detail)
726       | 4 -> `Resumed (Resumed.make detail)
727       | 5 -> `Stopped (Stopped.make detail)
728       | 6 -> `Shutdown
729       | 7 -> `PMSuspended (PM_suspended.make detail)
730       | x -> `Unknown x
731   end
732
733   module Reboot = struct
734     type t = unit
735
736     let to_string _ = "()"
737
738     let make () = ()
739   end
740
741   module Rtc_change = struct
742     type t = int64
743
744     let to_string = Int64.to_string
745
746     let make x = x
747   end
748
749   module Watchdog = struct
750     type t = [
751       | `None
752       | `Pause
753       | `Reset
754       | `Poweroff
755       | `Shutdown
756       | `Debug
757       | `Unknown of int
758     ]
759
760     let to_string = function
761       | `None -> "None"
762       | `Pause -> "Pause"
763       | `Reset -> "Reset"
764       | `Poweroff -> "Poweroff"
765       | `Shutdown -> "Shutdown"
766       | `Debug -> "Debug"
767       | `Unknown x -> Printf.sprintf "Unknown watchdog_action: %d" x
768
769     let make = function
770       | 0 -> `None
771       | 1 -> `Pause
772       | 2 -> `Reset
773       | 3 -> `Poweroff
774       | 4 -> `Shutdown
775       | 5 -> `Debug
776       | x -> `Unknown x (* newer libvirt *)
777   end
778
779   module Io_error = struct
780     type action = [
781       | `None
782       | `Pause
783       | `Report
784       | `Unknown of int (* newer libvirt *)
785     ]
786
787     let string_of_action = function
788       | `None -> "None"
789       | `Pause -> "Pause"
790       | `Report -> "Report"
791       | `Unknown x -> Printf.sprintf "Unknown Io_error.action: %d" x
792
793     let action_of_int = function
794       | 0 -> `None
795       | 1 -> `Pause
796       | 2 -> `Report
797       | x -> `Unknown x
798
799     type t = {
800       src_path: string option;
801       dev_alias: string option;
802       action: action;
803       reason: string option;
804     }
805
806     let to_string t = Printf.sprintf
807         "{ Io_error.src_path = %s; dev_alias = %s; action = %s; reason = %s }"
808         (string_option t.src_path)
809         (string_option t.dev_alias)
810         (string_of_action t.action)
811         (string_option t.reason)
812
813     let make (src_path, dev_alias, action, reason) = {
814         src_path = src_path;
815         dev_alias = dev_alias;
816         action = action_of_int action;
817         reason = reason;
818     }
819
820     let make_noreason (src_path, dev_alias, action) =
821       make (src_path, dev_alias, action, None)
822   end
823
824   module Graphics_address = struct
825     type family = [
826       | `Ipv4
827       | `Ipv6
828       | `Unix
829       | `Unknown of int (* newer libvirt *)
830     ]
831
832     let string_of_family = function
833       | `Ipv4 -> "IPv4"
834       | `Ipv6 -> "IPv6"
835       | `Unix -> "UNIX"
836       | `Unknown x -> Printf.sprintf "Unknown Graphics_address.family: %d" x
837
838     let family_of_int = function
839       (* no zero *)
840       | 1 -> `Ipv4
841       | 2 -> `Ipv6
842       | 3 -> `Unix
843       | x -> `Unknown x
844
845     type t = {
846       family: family;         (** Address family *)
847       node: string option;    (** Address of node (eg IP address, or UNIX path *)
848       service: string option; (** Service name/number (eg TCP port, or NULL) *)
849     }
850
851     let to_string t = Printf.sprintf
852       "{ family = %s; node = %s; service = %s }"
853         (string_of_family t.family)
854         (string_option t.node)
855         (string_option t.service)
856
857     let make (family, node, service) = {
858       family = family_of_int family;
859       node = node;
860       service = service;
861     }
862   end
863
864   module Graphics_subject = struct
865     type identity = {
866       ty: string option;
867       name: string option;
868     }
869
870     let string_of_identity t = Printf.sprintf
871       "{ ty = %s; name = %s }"
872       (string_option t.ty)
873       (string_option t.name)
874
875     type t = identity list
876
877     let to_string ts =
878       "[ " ^ (String.concat "; " (List.map string_of_identity ts)) ^ " ]"
879
880     let make xs =
881       List.map (fun (ty, name) -> { ty = ty; name = name })
882         (Array.to_list xs)
883   end
884
885   module Graphics = struct
886     type phase = [
887       | `Connect
888       | `Initialize
889       | `Disconnect
890       | `Unknown of int (** newer libvirt *)
891     ]
892
893     let string_of_phase = function
894       | `Connect -> "Connect"
895       | `Initialize -> "Initialize"
896       | `Disconnect -> "Disconnect"
897       | `Unknown x -> Printf.sprintf "Unknown Graphics.phase: %d" x
898
899     let phase_of_int = function
900       | 0 -> `Connect
901       | 1 -> `Initialize
902       | 2 -> `Disconnect
903       | x -> `Unknown x
904
905     type t = {
906       phase: phase;                (** the phase of the connection *)
907       local: Graphics_address.t;   (** the local server address *)
908       remote: Graphics_address.t;  (** the remote client address *)
909       auth_scheme: string option;  (** the authentication scheme activated *)
910       subject: Graphics_subject.t; (** the authenticated subject (user) *)
911     }
912
913     let to_string t =
914       let phase = Printf.sprintf "phase = %s"
915         (string_of_phase t.phase) in
916       let local = Printf.sprintf "local = %s"
917         (Graphics_address.to_string t.local) in
918       let remote = Printf.sprintf "remote = %s"
919         (Graphics_address.to_string t.remote) in
920       let auth_scheme = Printf.sprintf "auth_scheme = %s"
921         (string_option t.auth_scheme) in
922       let subject = Printf.sprintf "subject = %s"
923         (Graphics_subject.to_string t.subject) in
924       "{ " ^ (String.concat "; " [ phase; local; remote; auth_scheme; subject ]) ^ " }"
925
926     let make (phase, local, remote, auth_scheme, subject) = {
927       phase = phase_of_int phase;
928       local = Graphics_address.make local;
929       remote = Graphics_address.make remote;
930       auth_scheme = auth_scheme;
931       subject = Graphics_subject.make subject;
932     }
933   end
934
935   module Control_error = struct
936     type t = unit
937
938     let to_string () = "()"
939
940     let make () = ()
941   end
942
943   module Block_job = struct
944     type ty = [
945       | `KnownUnknown (* explicitly named UNKNOWN in the spec *)
946       | `Pull
947       | `Copy
948       | `Commit
949       | `Unknown of int (* newer libvirt *)
950     ]
951
952     let string_of_ty = function
953       | `KnownUnknown -> "KnownUnknown"
954       | `Pull -> "Pull"
955       | `Copy -> "Copy"
956       | `Commit -> "Commit"
957       | `Unknown x -> Printf.sprintf "Unknown Block_job.ty: %d" x
958
959     let ty_of_int = function
960       | 0 -> `KnownUnknown
961       | 1 -> `Pull
962       | 2 -> `Copy
963       | 3 -> `Commit
964       | x -> `Unknown x (* newer libvirt *)
965
966     type status = [
967       | `Completed
968       | `Failed
969       | `Cancelled
970       | `Ready
971       | `Unknown of int
972     ]
973
974     let string_of_status = function
975       | `Completed -> "Completed"
976       | `Failed -> "Failed"
977       | `Cancelled -> "Cancelled"
978       | `Ready -> "Ready"
979       | `Unknown x -> Printf.sprintf "Unknown Block_job.status: %d" x
980
981     let status_of_int = function
982       | 0 -> `Completed
983       | 1 -> `Failed
984       | 2 -> `Cancelled
985       | 3 -> `Ready
986       | x -> `Unknown x
987
988     type t = {
989       disk: string option;
990       ty: ty;
991       status: status;
992     }
993
994     let to_string t = Printf.sprintf "{ disk = %s; ty = %s; status = %s }"
995       (string_option t.disk)
996       (string_of_ty t.ty)
997       (string_of_status t.status)
998
999     let make (disk, ty, status) = {
1000       disk = disk;
1001       ty = ty_of_int ty;
1002       status = status_of_int ty;
1003     }
1004   end
1005
1006   module Disk_change = struct
1007     type reason = [
1008       | `MissingOnStart
1009       | `Unknown of int
1010     ]
1011
1012     let string_of_reason = function
1013       | `MissingOnStart -> "MissingOnStart"
1014       | `Unknown x -> Printf.sprintf "Unknown Disk_change.reason: %d" x
1015
1016     let reason_of_int = function
1017       | 0 -> `MissingOnStart
1018       | x -> `Unknown x
1019
1020     type t = {
1021       old_src_path: string option;
1022       new_src_path: string option;
1023       dev_alias: string option;
1024       reason: reason;
1025     }
1026
1027     let to_string t =
1028       let o = Printf.sprintf "old_src_path = %s" (string_option t.old_src_path) in
1029       let n = Printf.sprintf "new_src_path = %s" (string_option t.new_src_path) in
1030       let d = Printf.sprintf "dev_alias = %s" (string_option t.dev_alias) in
1031       let r = string_of_reason t.reason in
1032       "{ " ^ (String.concat "; " [ o; n; d; r ]) ^ " }"
1033
1034     let make (o, n, d, r) = {
1035       old_src_path = o;
1036       new_src_path = n;
1037       dev_alias = d;
1038       reason = reason_of_int r;
1039     }
1040   end
1041
1042   module Tray_change = struct
1043     type reason = [
1044       | `Open
1045       | `Close
1046       | `Unknown of int
1047     ]
1048
1049     let string_of_reason = function
1050       | `Open -> "Open"
1051       | `Close -> "Close"
1052       | `Unknown x -> Printf.sprintf "Unknown Tray_change.reason: %d" x
1053
1054     let reason_of_int = function
1055       | 0 -> `Open
1056       | 1 -> `Close
1057       | x -> `Unknown x
1058
1059     type t = {
1060       dev_alias: string option;
1061       reason: reason;
1062     }
1063
1064     let to_string t = Printf.sprintf
1065       "{ dev_alias = %s; reason = %s }"
1066         (string_option t.dev_alias)
1067         (string_of_reason t.reason)
1068
1069     let make (dev_alias, reason) = {
1070       dev_alias = dev_alias;
1071       reason = reason_of_int reason;
1072     }
1073   end
1074
1075   module PM_wakeup = struct
1076     type reason = [
1077       | `Unknown of int
1078     ]
1079
1080     type t = reason
1081
1082     let to_string = function
1083       | `Unknown x -> Printf.sprintf "Unknown PM_wakeup.reason: %d" x
1084
1085     let make x = `Unknown x
1086   end
1087
1088   module PM_suspend = struct
1089     type reason = [
1090       | `Unknown of int
1091     ]
1092
1093     type t = reason
1094
1095     let to_string = function
1096       | `Unknown x -> Printf.sprintf "Unknown PM_suspend.reason: %d" x
1097
1098     let make x = `Unknown x
1099   end
1100
1101   module Balloon_change = struct
1102     type t = int64
1103
1104     let to_string = Int64.to_string
1105     let make x = x
1106   end
1107
1108   module PM_suspend_disk = struct
1109     type reason = [
1110       | `Unknown of int
1111     ]
1112
1113     type t = reason
1114
1115     let to_string = function
1116       | `Unknown x -> Printf.sprintf "Unknown PM_suspend_disk.reason: %d" x
1117
1118     let make x = `Unknown x
1119   end
1120
1121   type callback =
1122     | Lifecycle     of ([`R] Domain.t -> Lifecycle.t -> unit)
1123     | Reboot        of ([`R] Domain.t -> Reboot.t -> unit)
1124     | RtcChange     of ([`R] Domain.t -> Rtc_change.t -> unit)
1125     | Watchdog      of ([`R] Domain.t -> Watchdog.t -> unit)
1126     | IOError       of ([`R] Domain.t -> Io_error.t -> unit)
1127     | Graphics      of ([`R] Domain.t -> Graphics.t -> unit)
1128     | IOErrorReason of ([`R] Domain.t -> Io_error.t -> unit)
1129     | ControlError  of ([`R] Domain.t -> Control_error.t -> unit)
1130     | BlockJob      of ([`R] Domain.t -> Block_job.t -> unit)
1131     | DiskChange    of ([`R] Domain.t -> Disk_change.t -> unit)
1132     | TrayChange    of ([`R] Domain.t -> Tray_change.t -> unit)
1133     | PMWakeUp      of ([`R] Domain.t -> PM_wakeup.t -> unit)
1134     | PMSuspend     of ([`R] Domain.t -> PM_suspend.t -> unit)
1135     | BalloonChange of ([`R] Domain.t -> Balloon_change.t -> unit)
1136     | PMSuspendDisk of ([`R] Domain.t -> PM_suspend_disk.t -> unit)
1137
1138   type callback_id = int64
1139
1140   let fresh_callback_id =
1141     let next = ref 0L in
1142     fun () ->
1143       let result = !next in
1144       next := Int64.succ !next;
1145       result
1146
1147   let make_table value_name =
1148     let table = Hashtbl.create 16 in
1149     let callback callback_id generic x =
1150       if Hashtbl.mem table callback_id
1151       then Hashtbl.find table callback_id generic x in
1152     let _ = Callback.register value_name callback in
1153     table
1154
1155   let u_table = make_table "Libvirt.u_callback"
1156   let i_table = make_table "Libvirt.i_callback"
1157   let i64_table = make_table "Libvirt.i64_callback"
1158   let i_i_table = make_table "Libvirt.i_i_callback"
1159   let s_i_table = make_table "Libvirt.s_i_callback"
1160   let s_i_i_table = make_table "Libvirt.s_i_i_callback"
1161   let s_s_i_table = make_table "Libvirt.s_s_i_callback"
1162   let s_s_i_s_table = make_table "Libvirt.s_s_i_s_callback"
1163   let s_s_s_i_table = make_table "Libvirt.s_s_s_i_callback"
1164   let i_ga_ga_s_gs_table = make_table "Libvirt.i_ga_ga_s_gs_callback"
1165
1166   external register_default_impl : unit -> unit = "ocaml_libvirt_event_register_default_impl"
1167
1168   external run_default_impl : unit -> unit = "ocaml_libvirt_event_run_default_impl"
1169
1170   external register_any' : 'a Connect.t -> 'a Domain.t option -> callback -> callback_id -> int = "ocaml_libvirt_connect_domain_event_register_any"
1171
1172   external deregister_any' : 'a Connect.t -> int -> unit = "ocaml_libvirt_connect_domain_event_deregister_any"
1173
1174   let our_id_to_libvirt_id = Hashtbl.create 16
1175
1176   let register_any conn ?dom callback =
1177     let id = fresh_callback_id () in
1178     begin match callback with
1179     | Lifecycle f ->
1180         Hashtbl.add i_i_table id (fun dom x ->
1181             f dom (Lifecycle.make x)
1182         )
1183     | Reboot f ->
1184         Hashtbl.add u_table id (fun dom x ->
1185             f dom (Reboot.make x)
1186         )
1187     | RtcChange f ->
1188         Hashtbl.add i64_table id (fun dom x ->
1189             f dom (Rtc_change.make x)
1190         )
1191     | Watchdog f ->
1192         Hashtbl.add i_table id (fun dom x ->
1193             f dom (Watchdog.make x)
1194         ) 
1195     | IOError f ->
1196         Hashtbl.add s_s_i_table id (fun dom x ->
1197             f dom (Io_error.make_noreason x)
1198         )
1199     | Graphics f ->
1200         Hashtbl.add i_ga_ga_s_gs_table id (fun dom x ->
1201             f dom (Graphics.make x)
1202         )
1203     | IOErrorReason f ->
1204         Hashtbl.add s_s_i_s_table id (fun dom x ->
1205             f dom (Io_error.make x)
1206         )
1207     | ControlError f ->
1208         Hashtbl.add u_table id (fun dom x ->
1209             f dom (Control_error.make x)
1210         )
1211     | BlockJob f ->
1212         Hashtbl.add s_i_i_table id (fun dom x ->
1213             f dom (Block_job.make x)
1214         )
1215     | DiskChange f ->
1216         Hashtbl.add s_s_s_i_table id (fun dom x ->
1217             f dom (Disk_change.make x)
1218         )
1219     | TrayChange f ->
1220         Hashtbl.add s_i_table id (fun dom x ->
1221             f dom (Tray_change.make x)
1222         )
1223     | PMWakeUp f ->
1224         Hashtbl.add i_table id (fun dom x ->
1225             f dom (PM_wakeup.make x)
1226         )
1227     | PMSuspend f ->
1228         Hashtbl.add i_table id (fun dom x ->
1229             f dom (PM_suspend.make x)
1230         )
1231     | BalloonChange f ->
1232         Hashtbl.add i64_table id (fun dom x ->
1233             f dom (Balloon_change.make x)
1234         )
1235     | PMSuspendDisk f ->
1236         Hashtbl.add i_table id (fun dom x ->
1237             f dom (PM_suspend_disk.make x)
1238         )
1239     end;
1240     let libvirt_id = register_any' conn dom callback id in
1241     Hashtbl.replace our_id_to_libvirt_id id libvirt_id;
1242     id
1243
1244   let deregister_any conn id =
1245     if Hashtbl.mem our_id_to_libvirt_id id then begin
1246       let libvirt_id = Hashtbl.find our_id_to_libvirt_id id in
1247       deregister_any' conn libvirt_id
1248     end;
1249     Hashtbl.remove our_id_to_libvirt_id id;
1250     Hashtbl.remove u_table id;
1251     Hashtbl.remove i_table id;
1252     Hashtbl.remove i64_table id;
1253     Hashtbl.remove i_i_table id;
1254     Hashtbl.remove s_i_table id;
1255     Hashtbl.remove s_i_i_table id;
1256     Hashtbl.remove s_s_i_table id;
1257     Hashtbl.remove s_s_i_s_table id;
1258     Hashtbl.remove s_s_s_i_table id;
1259     Hashtbl.remove i_ga_ga_s_gs_table id
1260
1261   let timeout_table = Hashtbl.create 16
1262   let _ =
1263     let callback x =
1264       if Hashtbl.mem timeout_table x
1265       then Hashtbl.find timeout_table x () in
1266   Callback.register "Libvirt.timeout_callback" callback
1267
1268   type timer_id = int64
1269
1270   external add_timeout' : 'a Connect.t -> int -> int64 -> int = "ocaml_libvirt_event_add_timeout"
1271
1272   external remove_timeout' : 'a Connect.t -> int -> unit = "ocaml_libvirt_event_remove_timeout"
1273
1274   let our_id_to_timer_id = Hashtbl.create 16
1275   let add_timeout conn ms fn =
1276     let id = fresh_callback_id () in
1277     Hashtbl.add timeout_table id fn;
1278     let timer_id = add_timeout' conn ms id in
1279     Hashtbl.add our_id_to_timer_id id timer_id;
1280     id
1281
1282   let remove_timeout conn id =
1283     if Hashtbl.mem our_id_to_timer_id id then begin
1284       let timer_id = Hashtbl.find our_id_to_timer_id id in
1285       remove_timeout' conn timer_id
1286     end;
1287     Hashtbl.remove our_id_to_timer_id id;
1288     Hashtbl.remove timeout_table id
1289 end
1290
1291 module Network =
1292 struct
1293   type 'rw t
1294
1295   external lookup_by_name : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_network_lookup_by_name"
1296   external lookup_by_uuid : 'a Connect.t -> uuid -> 'a t = "ocaml_libvirt_network_lookup_by_uuid"
1297   external lookup_by_uuid_string : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_network_lookup_by_uuid_string"
1298   external create_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_network_create_xml"
1299   external define_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_network_define_xml"
1300   external undefine : [>`W] t -> unit = "ocaml_libvirt_network_undefine"
1301   external create : [>`W] t -> unit = "ocaml_libvirt_network_create"
1302   external destroy : [>`W] t -> unit = "ocaml_libvirt_network_destroy"
1303   external free : [>`R] t -> unit = "ocaml_libvirt_network_free"
1304   external get_name : [>`R] t -> string = "ocaml_libvirt_network_get_name"
1305   external get_uuid : [>`R] t -> uuid = "ocaml_libvirt_network_get_uuid"
1306   external get_uuid_string : [>`R] t -> string = "ocaml_libvirt_network_get_uuid_string"
1307   external get_xml_desc : [>`R] t -> xml = "ocaml_libvirt_network_get_xml_desc"
1308   external get_bridge_name : [>`R] t -> string = "ocaml_libvirt_network_get_bridge_name"
1309   external get_autostart : [>`R] t -> bool = "ocaml_libvirt_network_get_autostart"
1310   external set_autostart : [>`W] t -> bool -> unit = "ocaml_libvirt_network_set_autostart"
1311
1312   external const : [>`R] t -> ro t = "%identity"
1313 end
1314
1315 module Pool =
1316 struct
1317   type 'rw t
1318   type pool_state = Inactive | Building | Running | Degraded
1319   type pool_build_flags = New | Repair | Resize
1320   type pool_delete_flags = Normal | Zeroed
1321   type pool_info = {
1322     state : pool_state;
1323     capacity : int64;
1324     allocation : int64;
1325     available : int64;
1326   }
1327
1328   external lookup_by_name : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_pool_lookup_by_name"
1329   external lookup_by_uuid : 'a Connect.t -> uuid -> 'a t = "ocaml_libvirt_storage_pool_lookup_by_uuid"
1330   external lookup_by_uuid_string : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_pool_lookup_by_uuid_string"
1331   external create_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_storage_pool_create_xml"
1332   external define_xml : [>`W] Connect.t -> xml -> rw t = "ocaml_libvirt_storage_pool_define_xml"
1333   external build : [>`W] t -> pool_build_flags -> unit = "ocaml_libvirt_storage_pool_build"
1334   external undefine : [>`W] t -> unit = "ocaml_libvirt_storage_pool_undefine"
1335   external create : [>`W] t -> unit = "ocaml_libvirt_storage_pool_create"
1336   external destroy : [>`W] t -> unit = "ocaml_libvirt_storage_pool_destroy"
1337   external delete : [>`W] t -> unit = "ocaml_libvirt_storage_pool_delete"
1338   external free : [>`R] t -> unit = "ocaml_libvirt_storage_pool_free"
1339   external refresh : [`R] t -> unit = "ocaml_libvirt_storage_pool_refresh"
1340   external get_name : [`R] t -> string = "ocaml_libvirt_storage_pool_get_name"
1341   external get_uuid : [`R] t -> uuid = "ocaml_libvirt_storage_pool_get_uuid"
1342   external get_uuid_string : [`R] t -> string = "ocaml_libvirt_storage_pool_get_uuid_string"
1343   external get_info : [`R] t -> pool_info = "ocaml_libvirt_storage_pool_get_info"
1344   external get_xml_desc : [`R] t -> xml = "ocaml_libvirt_storage_pool_get_xml_desc"
1345   external get_autostart : [`R] t -> bool = "ocaml_libvirt_storage_pool_get_autostart"
1346   external set_autostart : [>`W] t -> bool -> unit = "ocaml_libvirt_storage_pool_set_autostart"
1347   external num_of_volumes : [`R] t -> int = "ocaml_libvirt_storage_pool_num_of_volumes"
1348   external list_volumes : [`R] t -> int -> string array = "ocaml_libvirt_storage_pool_list_volumes"
1349   external const : [>`R] t -> ro t = "%identity"
1350 end
1351
1352 module Volume =
1353 struct
1354   type 'rw t
1355   type vol_type = File | Block
1356   type vol_delete_flags = Normal | Zeroed
1357   type vol_info = {
1358     typ : vol_type;
1359     capacity : int64;
1360     allocation : int64;
1361   }
1362
1363   external lookup_by_name : 'a Pool.t -> string -> 'a t = "ocaml_libvirt_storage_vol_lookup_by_name"
1364   external lookup_by_key : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_vol_lookup_by_key"
1365   external lookup_by_path : 'a Connect.t -> string -> 'a t = "ocaml_libvirt_storage_vol_lookup_by_path"
1366   external pool_of_volume : 'a t -> 'a Pool.t = "ocaml_libvirt_storage_pool_lookup_by_volume"
1367   external get_name : [`R] t -> string = "ocaml_libvirt_storage_vol_get_name"
1368   external get_key : [`R] t -> string = "ocaml_libvirt_storage_vol_get_key"
1369   external get_path : [`R] t -> string = "ocaml_libvirt_storage_vol_get_path"
1370   external get_info : [`R] t -> vol_info = "ocaml_libvirt_storage_vol_get_info"
1371   external get_xml_desc : [`R] t -> xml = "ocaml_libvirt_storage_vol_get_xml_desc"
1372   external create_xml : [>`W] Pool.t -> xml -> unit = "ocaml_libvirt_storage_vol_create_xml"
1373   external delete : [>`W] t -> vol_delete_flags -> unit = "ocaml_libvirt_storage_vol_delete"
1374   external free : [>`R] t -> unit = "ocaml_libvirt_storage_vol_free"
1375   external const : [>`R] t -> ro t = "%identity"
1376 end
1377
1378 (* Initialization. *)
1379 external c_init : unit -> unit = "ocaml_libvirt_init"
1380 let () =
1381   Callback.register_exception
1382     "ocaml_libvirt_virterror" (Virterror (Virterror.no_error ()));
1383   Callback.register_exception
1384     "ocaml_libvirt_not_supported" (Not_supported "");
1385   c_init ()