Version 0.0.1
[guestfs-browser.git] / slave.ml
1 (* Guestfs Browser.
2  * Copyright (C) 2010 Red Hat Inc.
3  *
4  * This program is free software; you can redistribute it and/or modify
5  * it under the terms of the GNU General Public License as published by
6  * the Free Software Foundation; either version 2 of the License, or
7  * (at your option) any later version.
8  *
9  * This program is distributed in the hope that it will be useful,
10  * but WITHOUT ANY WARRANTY; without even the implied warranty of
11  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12  * GNU General Public License for more details.
13  *
14  * You should have received a copy of the GNU General Public License along
15  * with this program; if not, write to the Free Software Foundation, Inc.,
16  * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
17  *)
18
19 open ExtList
20 open Printf
21 open Utils
22
23 module C = Libvirt.Connect
24 module Cond = Condition
25 module D = Libvirt.Domain
26 module G = Guestfs
27 module M = Mutex
28 module Q = Queue
29
30 type 'a callback = 'a -> unit
31
32 (* The commands. *)
33 type command =
34   | Exit_thread
35   | Connect of string option * unit callback
36   | Get_domains of domain list callback
37   | Open_domain of string * rw_flag callback
38   | Open_images of string list * rw_flag callback
39   | Get_volumes of volume callback
40   | Read_directory of string * string * direntry list callback
41
42 and domain = {
43   dom_id : int;
44   dom_name : string;
45   dom_state : D.state;
46 }
47
48 and rw_flag = RO | RW
49
50 and volume = {
51   vol_device : string;
52   vol_type : string;
53   vol_label : string;
54   vol_uuid : string;
55   vol_statvfs : Guestfs.statvfs;
56 }
57
58 and direntry = {
59   dent_name : string;
60   dent_stat : Guestfs.stat;
61   dent_link : string;
62 }
63
64 let string_of_command = function
65   | Exit_thread -> "Exit_thread"
66   | Connect (Some name, _) -> sprintf "Connect %s" name
67   | Connect (None, _) -> "Connect NULL"
68   | Get_domains _ -> "Get_domains"
69   | Open_domain (name, _) -> sprintf "Open_domain %s" name
70   | Open_images (images, _) ->
71       sprintf "Open_images [%s]" (String.concat "; " images)
72   | Get_volumes _ -> "Get_volumes"
73   | Read_directory (dev, dir, _) -> sprintf "Read_directory %s %s" dev dir
74
75 let string_of_rw_flag = function RO -> "RO" | RW -> "RW"
76
77 let no_callback _ = ()
78
79 let failure_hook = ref (fun _ -> ())
80 let busy_hook = ref (fun _ -> ())
81 let idle_hook = ref (fun _ -> ())
82
83 let set_failure_hook cb = failure_hook := cb
84 let set_busy_hook cb = busy_hook := cb
85 let set_idle_hook cb = idle_hook := cb
86
87 (* Execute a function, while holding a mutex.  If the function
88  * fails, ensure we release the mutex before rethrowing the
89  * exception.
90  *)
91 let with_lock m f =
92   M.lock m;
93   let r = try Left (f ()) with exn -> Right exn in
94   M.unlock m;
95   match r with
96   | Left r -> r
97   | Right exn -> raise exn
98
99 (* The queue of commands, and a lock and condition to protect it. *)
100 let q = Q.create ()
101 let q_lock = M.create ()
102 let q_cond = Cond.create ()
103
104 (* Send a command message to the slave thread. *)
105 let send_to_slave cmd =
106   debug "sending message %s to slave thread ..." (string_of_command cmd);
107   with_lock q_lock (
108     fun () ->
109       Q.push cmd q;
110       Cond.signal q_cond
111   )
112
113 let discard_command_queue () = with_lock q_lock (fun () -> Q.clear q)
114
115 let connect uri cb = send_to_slave (Connect (uri, cb))
116 let get_domains cb = send_to_slave (Get_domains cb)
117 let get_volumes cb = send_to_slave (Get_volumes cb)
118 let open_domain name cb = send_to_slave (Open_domain (name, cb))
119 let open_images images cb = send_to_slave (Open_images (images, cb))
120 let read_directory dev dir cb = send_to_slave (Read_directory (dev, dir, cb))
121
122 (*----- Slave thread starts here -----*)
123
124 (* Set this to true to exit the thread. *)
125 let quit = ref false
126
127 (* Handles.  These are not protected by locks because only the slave
128  * thread has access to them.
129  *)
130 let conn = ref None
131 let g = ref None
132
133 (* Call 'f ()' with 'dev' mounted read-only.  Ensure that everything
134  * is unmounted even if an exception is thrown.
135  *)
136 let with_mount_ro g dev (f : unit -> 'a) : 'a =
137   Std.finally (fun () -> G.umount_all g) (
138     fun () ->
139       G.mount_ro g dev "/";
140       f ()
141   ) ()
142
143 let rec loop () =
144   (* Get the next command. *)
145   let cmd =
146     with_lock q_lock (
147       fun () ->
148         while Q.is_empty q do
149           Cond.wait q_cond q_lock
150         done;
151         Q.pop q
152     ) in
153
154   debug "thread id %d: slave processing command %s ..."
155     (Thread.id (Thread.self ())) (string_of_command cmd);
156
157   (try
158      GtkThread.async !busy_hook ();
159      execute_command cmd;
160    with exn ->
161      (* If a command fails, clear the command queue and run the
162       * failure hook in the main thread.
163       *)
164      discard_command_queue ();
165      GtkThread.async !failure_hook exn
166   );
167
168   (* If there are no more commands in the queue, run the idle hook. *)
169   let r = with_lock q_lock (fun () -> Q.is_empty q) in
170   if r then GtkThread.async !idle_hook ();
171
172   if !quit then Thread.exit ();
173   loop ()
174
175 and execute_command = function
176   | Exit_thread ->
177       quit := true;
178       close_all ()
179
180   | Connect (name, cb) ->
181       close_all ();
182       conn := Some (C.connect_readonly ?name ());
183       GtkThread.async cb ()
184
185   | Get_domains cb ->
186       let conn = get_conn () in
187       let doms = D.get_domains conn [D.ListAll] in
188       let doms = List.map (
189         fun d ->
190           { dom_id = D.get_id d;
191             dom_name = D.get_name d;
192             dom_state = (D.get_info d).D.state }
193       ) doms in
194       let cmp { dom_name = n1 } { dom_name = n2 } = compare n1 n2 in
195       let doms = List.sort ~cmp doms in
196       GtkThread.async cb doms
197
198   | Open_domain (name, cb) ->
199       let conn = get_conn () in
200       let dom = D.lookup_by_name conn name in
201       (* Only permit writes to shut off domains.  This isn't foolproof
202        * since the user could start up the domain while we're running,
203        * which would cause disk corruption.  Until we can negotiate a
204        * feasible locking scheme with libvirt/qemu, this is the best we
205        * can do.
206        *)
207       let rw = write_flag () && (D.get_info dom).D.state = D.InfoShutoff in
208       let rw = if rw then RW else RO in
209       let xml = D.get_xml_desc dom in
210       let images = get_disk_images_from_xml xml in
211       open_disk_images rw images cb
212
213   | Open_images (images, cb) ->
214       let rw = write_flag () in
215       let rw = if rw then RW else RO in
216       open_disk_images rw images cb
217
218   | Get_volumes cb ->
219       let g = get_g () in
220       (* Devices which directly contain filesystems (RHBZ#590167). *)
221       let devices = G.list_devices g in
222       Array.iter (if_mountable_vol g cb) devices;
223       let partitions = G.list_partitions g in
224       Array.iter (if_mountable_vol g cb) partitions;
225       let lvs = G.lvs g in
226       Array.iter (if_mountable_vol g cb) lvs
227
228   | Read_directory (dev, dir, cb) ->
229       let g = get_g () in
230       let names, stats, links =
231         with_mount_ro g dev (
232           fun () ->
233             let names = G.ls g dir in (* sorted and without . and .. *)
234             let names = Array.to_list names in
235             let stats = lstatlist_wrapper g dir names in
236             let links = readlinklist_wrapper g dir names in
237             names, stats, links
238         ) in
239       assert (
240         let n = List.length names in
241         n = List.length stats && n = List.length links
242       );
243       let entries = List.combine (List.combine names stats) links in
244       let entries = List.map (
245         fun ((name, stat), link) ->
246           { dent_name = name; dent_stat = stat; dent_link = link }
247       ) entries in
248       GtkThread.async cb entries
249
250 (* Expect to be connected, and return the current libvirt connection. *)
251 and get_conn () =
252   match !conn with
253   | Some conn -> conn
254   | None -> failwith "not connected to libvirt"
255
256 and get_g () =
257   match !g with
258   | Some g -> g
259   | None -> failwith "no domain or disk image is open"
260
261 (* Close all libvirt and libguestfs handles. *)
262 and close_all () =
263   (match !conn with Some conn -> C.close conn | None -> ());
264   conn := None;
265   close_g ()
266
267 and close_g () =
268   (match !g with Some g -> G.close g | None -> ());
269   g := None
270
271 and get_disk_images_from_xml xml =
272   let xml = Xml.parse_string xml in
273   let devices =
274     match xml with
275     | Xml.Element ("domain", _, children) ->
276         let devices =
277           List.filter_map (
278             function
279             | Xml.Element ("devices", _, devices) -> Some devices
280             | _ -> None
281           ) children in
282         List.concat devices
283     | _ ->
284         failwith "get_xml_desc didn't return <domain/>" in
285   let rec source_of = function          (* <source file|dev=...> *)
286     | [] -> None
287     | Xml.Element ("source", attrs, _) :: rest ->
288         (try Some (List.assoc "dev" attrs)
289          with Not_found ->
290            try Some (List.assoc "file" attrs)
291            with Not_found ->
292              source_of rest)
293     | _ :: rest -> source_of rest
294   in
295   let blkdevs =
296     List.filter_map (
297       function
298       | Xml.Element ("disk", _, children) -> source_of children
299       | _ -> None
300     ) devices in
301   blkdevs
302
303 (* The common code for Open_domain and Open_images which opens the
304  * libguestfs handle, adds the disks, and launches the appliance.
305  *)
306 and open_disk_images rw images cb =
307   debug "opening disk image [%s] in %s mode"
308     (String.concat "; " images) (string_of_rw_flag rw);
309
310   close_g ();
311   let g' = G.create () in
312   g := Some g';
313   let g = g' in
314
315   G.set_verbose g (verbose ());
316
317   let add = (match rw with RO -> G.add_drive_ro | RW -> G.add_drive) g in
318   List.iter add images;
319
320   G.launch g;
321   GtkThread.async cb rw
322
323 (* This is the common function implementing Get_volumes.  Test if a
324  * particular partition contains a mountable filesystem.  We do this
325  * simply by trying to mount it.  If it does, get the rest of the
326  * information for the volume, and call the callback.
327  *)
328 and if_mountable_vol g cb dev =
329   try
330     with_mount_ro g dev (
331       fun () ->
332         let vol_type = G.vfs_type g dev in
333         let vol_label = G.vfs_label g dev in
334         let vol_uuid = G.vfs_uuid g dev in
335         let vol_statvfs = G.statvfs g "/" in
336         let vol = {
337           vol_device = dev; vol_type = vol_type; vol_label = vol_label;
338           vol_uuid = vol_uuid; vol_statvfs = vol_statvfs
339         } in
340         GtkThread.async cb vol
341     )
342   with G.Error msg ->
343     debug "is_mountable: %s: not mountable because: %s" dev msg
344
345 (* guestfs_lstatlist has a "hidden" limit of the protocol message size.
346  * Call this function, but split the list of names into chunks.
347  *)
348 and lstatlist_wrapper g dir = function
349   | [] -> []
350   | names ->
351       let names', names = List.take 1000 names, List.drop 1000 names in
352       let xs = G.lstatlist g dir (Array.of_list names') in
353       let xs = Array.to_list xs in
354       xs @ lstatlist_wrapper g dir names
355
356 (* Same as above for guestfs_readlinklist. *)
357 and readlinklist_wrapper g dir = function
358   | [] -> []
359   | names ->
360       let names', names = List.take 1000 names, List.drop 1000 names in
361       let xs = G.readlinklist g dir (Array.of_list names') in
362       let xs = Array.to_list xs in
363       xs @ readlinklist_wrapper g dir names
364
365 (* Start up one slave thread. *)
366 let slave_thread = Thread.create loop ()
367
368 (* Note the following function is called from the main thread. *)
369 let exit_thread () =
370   discard_command_queue ();
371   send_to_slave Exit_thread;
372   Thread.join slave_thread