Daily check-in.
[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 M = Mutex
27 module Q = Queue
28
29 type 'a callback = 'a -> unit
30
31 (* The commands. *)
32 type command =
33   | Exit_thread
34   | Connect of string option * domain list callback
35   | Download_dir_find0 of source * string * string * unit callback
36   | Download_dir_tarball of source * string * download_dir_tarball_format * string * unit callback
37   | Download_file of source * string * string * unit callback
38   | Open_domain of string * inspection_data callback
39   | Open_images of (string * string option) list * inspection_data callback
40   | Read_directory of source * 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 inspection_data = {
49   insp_all_filesystems : (string * string) list;
50   insp_oses : inspection_os list;
51 }
52
53 and inspection_os = {
54   insp_root : string;
55   insp_arch : string;
56   insp_distro : string;
57   insp_filesystems : string array;
58   insp_hostname : string;
59   insp_major_version : int;
60   insp_minor_version : int;
61   insp_mountpoints : (string * string) list;
62   insp_package_format : string;
63   insp_package_management : string;
64   insp_product_name : string;
65   insp_type : string;
66   insp_windows_systemroot : string option;
67 }
68
69 and source = OS of inspection_os | Volume of string
70
71 and direntry = {
72   dent_name : string;
73   dent_stat : Guestfs.stat;
74   dent_link : string;
75 }
76
77 and download_dir_tarball_format = Tar | TGZ | TXZ
78
79 let rec string_of_command = function
80   | Exit_thread -> "Exit_thread"
81   | Connect (Some name, _) -> sprintf "Connect %s" name
82   | Connect (None, _) -> "Connect NULL"
83   | Download_dir_find0 (src, remotedir, localfile, _) ->
84       sprintf "Download_dir_find0 (%s, %s, %s)"
85         (string_of_source src) remotedir localfile
86   | Download_dir_tarball (src, remotedir, format, localfile, _) ->
87       sprintf "Download_dir_tarball (%s, %s, %s, %s)"
88         (string_of_source src) remotedir
89         (string_of_download_dir_tarball_format format) localfile
90   | Download_file (src, remotefile, localfile, _) ->
91       sprintf "Download_file (%s, %s, %s)"
92         (string_of_source src) remotefile localfile
93   | Open_domain (name, _) -> sprintf "Open_domain %s" name
94   | Open_images (images, _) ->
95       sprintf "Open_images %s" (string_of_images images)
96   | Read_directory (src, dir, _) ->
97       sprintf "Read_directory (%s, %s)" (string_of_source src) dir
98
99 and string_of_images images =
100   "[" ^
101     String.concat "; "
102     (List.map (function
103                | fn, None -> fn
104                | fn, Some format -> sprintf "%s (%s)" fn format)
105        images) ^ "]"
106
107 and string_of_source = function
108   | OS { insp_root = root } ->
109       sprintf "OS %s" root
110   | Volume dev ->
111       sprintf "Volume %s" dev
112
113 and string_of_download_dir_tarball_format = function
114   | Tar -> "Tar"
115   | TGZ -> "TGZ"
116   | TXZ -> "TXZ"
117
118 let no_callback _ = ()
119
120 let failure_hook = ref (fun _ -> ())
121 let busy_hook = ref (fun _ -> ())
122 let idle_hook = ref (fun _ -> ())
123 let progress_hook = ref (fun _ -> ())
124
125 let set_failure_hook cb = failure_hook := cb
126 let set_busy_hook cb = busy_hook := cb
127 let set_idle_hook cb = idle_hook := cb
128 let set_progress_hook cb = progress_hook := cb
129
130 (* Execute a function, while holding a mutex.  If the function
131  * fails, ensure we release the mutex before rethrowing the
132  * exception.
133  *)
134 let with_lock m f =
135   M.lock m;
136   let r = try Left (f ()) with exn -> Right exn in
137   M.unlock m;
138   match r with
139   | Left r -> r
140   | Right exn -> raise exn
141
142 (* The queue of commands, and a lock and condition to protect it. *)
143 let q = Q.create ()
144 let q_discard = ref false
145 let q_lock = M.create ()
146 let q_cond = Cond.create ()
147
148 (* Send a command message to the slave thread. *)
149 let send_to_slave ?fail cmd =
150   debug "sending message %s to slave thread ..." (string_of_command cmd);
151   with_lock q_lock (
152     fun () ->
153       Q.push (fail, cmd) q;
154       Cond.signal q_cond
155   )
156
157 let discard_command_queue () =
158   with_lock q_lock (
159     fun () ->
160       Q.clear q;
161       (* Discard the currently running command. *)
162       q_discard := true
163   )
164
165 let connect ?fail uri cb = send_to_slave ?fail (Connect (uri, cb))
166 let download_dir_find0 ?fail src remotedir localfile cb =
167   send_to_slave ?fail (Download_dir_find0 (src, remotedir, localfile, cb))
168 let download_dir_tarball ?fail src remotedir format localfile cb =
169   send_to_slave ?fail
170     (Download_dir_tarball (src, remotedir, format, localfile, cb))
171 let download_file ?fail src remotefile localfile cb =
172   send_to_slave ?fail (Download_file (src, remotefile, localfile, cb))
173 let open_domain ?fail name cb = send_to_slave ?fail (Open_domain (name, cb))
174 let open_images ?fail images cb = send_to_slave ?fail (Open_images (images, cb))
175 let read_directory ?fail src path cb =
176   send_to_slave ?fail (Read_directory (src, path, cb))
177
178 (*----- Slave thread starts here -----*)
179
180 (* Set this to true to exit the thread. *)
181 let quit = ref false
182
183 (* Handles.  These are not protected by locks because only the slave
184  * thread has access to them.
185  *)
186 let conn = ref None
187 let g = ref None
188
189 (* Run the callback unless someone set the q_discard flag while
190  * we were running the command.
191  *)
192 let callback_if_not_discarded (cb : 'a callback) (arg : 'a) =
193   let discard = with_lock q_lock (fun () -> !q_discard) in
194   if not discard then
195     GtkThread.async cb arg
196
197 (* Call 'f ()' with source mounted read-only.  Ensure that everything
198  * is unmounted even if an exception is thrown.
199  *)
200 let with_mount_ro g src (f : unit -> 'a) : 'a =
201   Std.finally (fun () -> g#umount_all ()) (
202     fun () ->
203       (* Do the mount - could be OS or single volume. *)
204       (match src with
205       | Volume dev -> g#mount_ro dev "/";
206       | OS { insp_mountpoints = mps } ->
207           (* Sort the mountpoint keys by length, shortest first. *)
208           let cmp (a,_) (b,_) = compare (String.length a) (String.length b) in
209           let mps = List.sort ~cmp mps in
210           (* Mount the filesystems. *)
211           List.iter (
212             fun (mp, dev) -> g#mount_ro dev mp
213           ) mps
214       );
215       f ()
216   ) ()
217
218 let rec loop () =
219   debug "top of slave loop";
220
221   (* Get the next command. *)
222   let fail, cmd =
223     with_lock q_lock (
224       fun () ->
225         while Q.is_empty q do Cond.wait q_cond q_lock done;
226         q_discard := false;
227         Q.pop q
228     ) in
229
230   debug "slave processing command %s ..." (string_of_command cmd);
231
232   (try
233      GtkThread.async !busy_hook ();
234      execute_command cmd
235    with exn ->
236      (* If the user provided an override ?fail parameter to the
237       * original call, call that, else call the global hook.
238       *)
239      match fail with
240      | Some cb -> GtkThread.async cb exn
241      | None -> GtkThread.async !failure_hook exn
242   );
243
244   (* If there are no more commands in the queue, run the idle hook. *)
245   let empty = with_lock q_lock (fun () -> Q.is_empty q) in
246   if empty then GtkThread.async !idle_hook ();
247
248   if !quit then Thread.exit ();
249   loop ()
250
251 and execute_command = function
252   | Exit_thread ->
253       quit := true;
254       close_all ()
255
256   | Connect (name, cb) ->
257       close_all ();
258       conn := Some (C.connect_readonly ?name ());
259
260       let conn = get_conn () in
261       let doms = D.get_domains conn [D.ListAll] in
262       let doms = List.map (
263         fun d ->
264           { dom_id = D.get_id d;
265             dom_name = D.get_name d;
266             dom_state = (D.get_info d).D.state }
267       ) doms in
268       let cmp { dom_name = n1 } { dom_name = n2 } = compare n1 n2 in
269       let doms = List.sort ~cmp doms in
270       callback_if_not_discarded cb doms
271
272   | Download_dir_find0 (src, remotedir, localfile, cb) ->
273       let g = get_g () in
274       with_mount_ro g src (
275         fun () ->
276           g#find0 remotedir localfile
277       );
278       callback_if_not_discarded cb ()
279
280   | Download_dir_tarball (src, remotedir, format, localfile, cb) ->
281       let g = get_g () in
282       let f = match format with
283         | Tar -> g#tar_out
284         | TGZ -> g#tgz_out
285         | TXZ -> g#txz_out
286       in
287       with_mount_ro g src (
288         fun () ->
289           f remotedir localfile
290       );
291       callback_if_not_discarded cb ()
292
293   | Download_file (src, remotefile, localfile, cb) ->
294       let g = get_g () in
295       with_mount_ro g src (
296         fun () ->
297           g#download remotefile localfile
298       );
299       callback_if_not_discarded cb ()
300
301   | Open_domain (name, cb) ->
302       let conn = get_conn () in
303       let dom = D.lookup_by_name conn name in
304       let xml = D.get_xml_desc dom in
305       let images = get_disk_images_from_xml xml in
306       open_disk_images images cb
307
308   | Open_images (images, cb) ->
309       open_disk_images images cb
310
311   | Read_directory (src, dir, cb) ->
312       let g = get_g () in
313       let names, stats, links =
314         with_mount_ro g src (
315           fun () ->
316             let names = g#ls dir in (* sorted and without . and .. *)
317             let names = Array.to_list names in
318             let stats = lstatlist_wrapper g dir names in
319             let links = readlinklist_wrapper g dir names in
320             names, stats, links
321         ) in
322       assert (
323         let n = List.length names in
324         n = List.length stats && n = List.length links
325       );
326       let entries = List.combine (List.combine names stats) links in
327       let entries = List.map (
328         fun ((name, stat), link) ->
329           { dent_name = name; dent_stat = stat; dent_link = link }
330       ) entries in
331       callback_if_not_discarded cb entries
332
333 (* Expect to be connected, and return the current libvirt connection. *)
334 and get_conn () =
335   match !conn with
336   | Some conn -> conn
337   | None -> failwith "not connected to libvirt"
338
339 and get_g () =
340   match !g with
341   | Some g -> g
342   | None -> failwith "no domain or disk image is open"
343
344 (* Close all libvirt and libguestfs handles. *)
345 and close_all () =
346   (match !conn with Some conn -> C.close conn | None -> ());
347   conn := None;
348   close_g ()
349
350 and close_g () =
351   (match !g with Some g -> g#close () | None -> ());
352   g := None
353
354 and get_disk_images_from_xml xml =
355   let xml = Xml.parse_string xml in
356
357   (* Return the device nodes. *)
358   let devices =
359     match xml with
360     | Xml.Element ("domain", _, children) ->
361         let devices =
362           List.filter_map (
363             function
364             | Xml.Element ("devices", _, devices) -> Some devices
365             | _ -> None
366           ) children in
367         List.concat devices
368     | _ ->
369         failwith "get_xml_desc didn't return <domain/>" in
370
371   (* Look for <source attr_name=attr_val/> and return attr_val. *)
372   let rec source_of attr_name = function
373     | [] -> None
374     | Xml.Element ("source", attrs, _) :: rest ->
375         (try Some (List.assoc attr_name attrs)
376          with Not_found -> source_of attr_name rest)
377     | _ :: rest -> source_of attr_name rest
378   in
379
380   (* Look for <driver type=attr_val/> and return attr_val. *)
381   let rec format_of = function
382     | [] -> None
383     | Xml.Element ("driver", attrs, _) :: rest ->
384         (try Some (List.assoc "type" attrs)
385          with Not_found -> format_of rest)
386     | _ :: rest -> format_of rest
387   in
388
389   (* Look for <disk> nodes and return the sources (block devices) of those. *)
390   let blkdevs =
391     List.filter_map (
392       function
393       | Xml.Element ("disk", attrs, disks) ->
394           let filename =
395             try
396               let typ = List.assoc "type" attrs in
397               if typ = "file" then source_of "file" disks
398               else if typ = "block" then source_of "dev" disks
399               else None
400             with
401               Not_found -> None in
402           (match filename with
403            | None -> None
404            | Some filename ->
405                let format = format_of disks in
406                Some (filename, format)
407           );
408       | _ -> None
409     ) devices in
410   blkdevs
411
412 (* The common code for Open_domain and Open_images which opens the
413  * libguestfs handle, adds the disks, and launches the appliance.
414  *)
415 and open_disk_images images cb =
416   debug "opening disk image %s" (string_of_images images);
417
418   close_g ();
419   let g' = new Guestfs.guestfs () in
420   g := Some g';
421   let g = g' in
422
423   g#set_trace (trace ());
424
425   (* Uncomment the next line to pass the verbose flag from the command
426    * line through to libguestfs.  This is not generally necessary since
427    * we are not so interested in debugging libguestfs problems at this
428    * level, and the user can always set LIBGUESTFS_DEBUG=1 if they need
429    * to.
430    *)
431   (* g#set_verbose (verbose ());*)
432
433   (* Attach progress bar callback. *)
434   g#set_progress_callback (
435     fun proc_nr serial position total ->
436       debug "progress callback proc_nr=%d serial=%d posn=%Ld total=%Ld"
437         proc_nr serial position total;
438       GtkThread.async !progress_hook (position, total)
439   );
440
441   List.iter (
442     function
443     | filename, None ->
444         g#add_drive_opts ~readonly:true filename
445     | filename, Some format ->
446         g#add_drive_opts ~readonly:true ~format filename
447   ) images;
448
449   g#launch ();
450
451   (* Get list of filesystems. *)
452   let fses = g#list_filesystems () in
453
454   (* Perform inspection.  This can fail, ignore errors. *)
455   let roots =
456     try Array.to_list (g#inspect_os ())
457     with
458       Guestfs.Error msg ->
459         debug "inspection failed (error ignored): %s" msg;
460         [] in
461
462   let oses = List.map (
463     fun root -> {
464       insp_root = root;
465       insp_arch = g#inspect_get_arch root;
466       insp_distro = g#inspect_get_distro root;
467       insp_filesystems = g#inspect_get_filesystems root;
468       insp_hostname = g#inspect_get_hostname root;
469       insp_major_version = g#inspect_get_major_version root;
470       insp_minor_version = g#inspect_get_minor_version root;
471       insp_mountpoints = g#inspect_get_mountpoints root;
472       insp_package_format = g#inspect_get_package_format root;
473       insp_package_management = g#inspect_get_package_management root;
474       insp_product_name = g#inspect_get_product_name root;
475       insp_type = g#inspect_get_type root;
476       insp_windows_systemroot =
477         try Some (g#inspect_get_windows_systemroot root)
478         with Guestfs.Error _ -> None
479     }
480   ) roots in
481   let data = {
482     insp_all_filesystems = fses;
483     insp_oses = oses;
484   } in
485   callback_if_not_discarded cb data
486
487 (* guestfs_lstatlist has a "hidden" limit of the protocol message size.
488  * Call this function, but split the list of names into chunks.
489  *)
490 and lstatlist_wrapper g dir = function
491   | [] -> []
492   | names ->
493       let names', names = List.take 1000 names, List.drop 1000 names in
494       let xs = g#lstatlist dir (Array.of_list names') in
495       let xs = Array.to_list xs in
496       xs @ lstatlist_wrapper g dir names
497
498 (* Same as above for guestfs_readlinklist. *)
499 and readlinklist_wrapper g dir = function
500   | [] -> []
501   | names ->
502       let names', names = List.take 1000 names, List.drop 1000 names in
503       let xs = g#readlinklist dir (Array.of_list names') in
504       let xs = Array.to_list xs in
505       xs @ readlinklist_wrapper g dir names
506
507 (* Start up one slave thread. *)
508 let slave_thread = Thread.create loop ()
509
510 (* Note the following function is called from the main thread. *)
511 let exit_thread () =
512   discard_command_queue ();
513   ignore (send_to_slave Exit_thread);
514   Thread.join slave_thread