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