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