Add Reopen option to the menu.
[guestfs-browser.git] / filetree.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 ExtString
20 open ExtList
21 open Unix
22 open Printf
23
24 open Utils
25 open DeviceSet
26 open Slave_types
27
28 open Filetree_markup
29
30 module G = Guestfs
31 module UTF8 = CamomileLibraryDefault.Camomile.UTF8
32
33 (* Temporary directory for shared use by any function in this file.
34  * It is cleaned up when the program exits.
35  *)
36 let tmpdir = tmpdir ()
37
38 (* The internal data we store attached to each row, telling us about
39  * the state of the row and what is in it.
40  *)
41 type hdata = {
42   mutable state : state_t;
43   content : content_t;
44   mutable visited : bool;
45   mutable hiveh : Hivex.t option;
46 }
47
48 (* The type of the hidden column used to implement on-demand loading.
49  * All rows are classified as either nodes or leafs (eg. a "node" might
50  * be a directory, or a top-level operating system, or anything else
51  * which the user could open and look inside).
52  *)
53 and state_t =
54   | IsLeaf           (* there are no children *)
55   | NodeNotStarted   (* user has not tried to open this *)
56   | NodeLoading      (* user tried to open it, still loading *)
57   | IsNode           (* we've loaded the children of this directory *)
58
59 (* The actual content of a row. *)
60 and content_t =
61   | Loading                          (* special "loading ..." node *)
62   | ErrorMessage of string           (* error message node *)
63   | Info of string                   (* information node (eg. disk usage) *)
64   | Top of Slave_types.source        (* top level OS or volume node *)
65   | TopWinReg of registry_t          (* top level Windows Registry node *)
66   | Directory of Slave_types.direntry(* a directory *)
67   | File of Slave_types.direntry     (* a file inc. special files *)
68   | RegKey of Hivex.node             (* a registry key (like a dir) *)
69   | RegValue of Hivex.value          (* a registry value (like a file) *)
70
71 (* Source, root key, remote filename, cache filename *)
72 and registry_t = Slave_types.source * string * string * string
73
74 let source_of_registry_t (src, _, _, _) = src
75 let root_key_of_registry_t (_, root_key, _, _) = root_key
76
77 (* This is the Filetree.tree class, derived from GTree.view
78  * (ie. GtkTreeView).
79  *)
80 class tree ?packing () =
81   let clear_tree = new GUtil.signal () in
82   let op_checksum_file = new GUtil.signal () in
83   let op_copy_regvalue = new GUtil.signal () in
84   let op_disk_usage = new GUtil.signal () in
85   let op_download_as_reg = new GUtil.signal () in
86   let op_download_dir_find0 = new GUtil.signal () in
87   let op_download_dir_tarball = new GUtil.signal () in
88   let op_download_file = new GUtil.signal () in
89   let op_file_information = new GUtil.signal () in
90   let op_inspection_dialog = new GUtil.signal () in
91   let op_view_file = new GUtil.signal () in
92
93   let view = GTree.view ?packing () in
94   (*view#set_rules_hint true;*)
95   (*view#selection#set_mode `MULTIPLE; -- add this later *)
96
97   (* Hash of index numbers -> hdata.  We do this because it's more
98    * efficient for the GC compared to storing OCaml objects directly in
99    * the rows.
100    *)
101   let hash = Hashtbl.create 1023 in
102
103   (* The columns stored in each row.  The hidden [index_col] column is
104    * an index into the hash table that records everything else about
105    * this row (see hdata above).  The other display columns, eg.
106    * [name_col] contain Pango markup and thus have to be escaped.
107    *)
108   let cols = new GTree.column_list in
109   (* Hidden: *)
110   let index_col = cols#add Gobject.Data.int in
111   (* Displayed: *)
112   let mode_col = cols#add Gobject.Data.string in
113   let name_col = cols#add Gobject.Data.string in
114   let size_col = cols#add Gobject.Data.string in
115   let date_col = cols#add Gobject.Data.string in
116
117   (* Create the model. *)
118   let model = GTree.tree_store cols in
119
120 object (self)
121   inherit GTree.view view#as_tree_view
122   inherit GUtil.ml_signals [clear_tree#disconnect;
123                             op_checksum_file#disconnect;
124                             op_copy_regvalue#disconnect;
125                             op_disk_usage#disconnect;
126                             op_download_as_reg#disconnect;
127                             op_download_dir_find0#disconnect;
128                             op_download_dir_tarball#disconnect;
129                             op_download_file#disconnect;
130                             op_file_information#disconnect;
131                             op_inspection_dialog#disconnect;
132                             op_view_file#disconnect]
133
134   initializer
135     (* Open a context menu when a button is pressed. *)
136     ignore (view#event#connect#button_press ~callback:self#button_press);
137
138     (* Create the view. *)
139     view#set_model (Some (model :> GTree.model));
140
141     (* Cell renderers. *)
142     let renderer = GTree.cell_renderer_text [], ["markup", mode_col] in
143     let mode_view = GTree.view_column ~title:"Permissions" ~renderer () in
144     mode_view#set_resizable true;
145     ignore (view#append_column mode_view);
146
147     let renderer = GTree.cell_renderer_text [], ["markup", name_col] in
148     let name_view = GTree.view_column ~title:"Filename" ~renderer () in
149     name_view#set_resizable true;
150     name_view#set_sizing `AUTOSIZE;
151     ignore (view#append_column name_view);
152
153     let renderer =
154       GTree.cell_renderer_text [`XALIGN 1.], ["markup", size_col] in
155     let size_view = GTree.view_column ~title:"Size" ~renderer () in
156     size_view#set_resizable true;
157     ignore (view#append_column size_view);
158
159     let renderer =
160       GTree.cell_renderer_text [`XALIGN 1.], ["markup", date_col] in
161     let date_view = GTree.view_column ~title:"Date" ~renderer () in
162     date_view#set_resizable true;
163     ignore (view#append_column date_view)
164
165   method clear () : unit =
166     model#clear ();
167     Hashtbl.clear hash;
168     clear_tree#call ()
169
170   method add_os name data : unit =
171     self#clear ();
172
173     (* Populate the top level of the filetree.  If there are operating
174      * systems from inspection, these have their own top level entries
175      * followed by only unreferenced filesystems.  If we didn't get
176      * anything from inspection, then at the top level we just show
177      * filesystems.
178      *)
179     let other_filesystems =
180       DeviceSet.of_list (List.map fst data.insp_all_filesystems) in
181     let other_filesystems =
182       List.fold_left (fun set { insp_filesystems = fses } ->
183                         DeviceSet.subtract set (DeviceSet.of_array fses))
184         other_filesystems data.insp_oses in
185
186     (* Add top level operating systems. *)
187     List.iter (self#add_top_level_os name) data.insp_oses;
188
189     (* Add top level left-over filesystems. *)
190     DeviceSet.iter (self#add_top_level_vol name) other_filesystems;
191
192     (* If it's Windows and registry files exist, create a node for
193      * each file.
194      *)
195     List.iter (
196       fun os ->
197         (match os.insp_winreg_SAM with
198          | Some filename ->
199              self#add_top_level_winreg name os "HKEY_LOCAL_MACHINE\\SAM"
200                filename
201          | None -> ()
202         );
203         (match os.insp_winreg_SECURITY with
204          | Some filename ->
205              self#add_top_level_winreg name os "HKEY_LOCAL_MACHINE\\SECURITY"
206                filename
207          | None -> ()
208         );
209         (match os.insp_winreg_SOFTWARE with
210          | Some filename ->
211              self#add_top_level_winreg name os "HKEY_LOCAL_MACHINE\\SOFTWARE"
212                filename
213          | None -> ()
214         );
215         (match os.insp_winreg_SYSTEM with
216          | Some filename ->
217              self#add_top_level_winreg name os "HKEY_LOCAL_MACHINE\\SYSTEM"
218                filename
219          | None -> ()
220         );
221         (match os.insp_winreg_DEFAULT with
222          | Some filename ->
223              self#add_top_level_winreg name os "HKEY_USERS\\.DEFAULT" filename
224          | None -> ()
225         );
226     ) data.insp_oses;
227
228     (* Expand the first top level node. *)
229     match model#get_iter_first with
230     | None -> ()
231     | Some row ->
232         self#expand_row (model#get_path row)
233
234   (* Add a top level operating system node. *)
235   method private add_top_level_os name os =
236     let markup =
237       sprintf "<b>%s</b>\n<small>%s</small>\n<small>%s</small>"
238         (markup_escape name) (markup_escape os.insp_hostname)
239         (markup_escape os.insp_product_name) in
240
241     let row = model#append () in
242     self#make_node row (Top (OS os)) None;
243     model#set ~row ~column:name_col markup
244
245   (* Add a top level volume (left over filesystem) node. *)
246   method private add_top_level_vol name dev =
247     let markup =
248       sprintf "<b>%s</b>\n<small>from %s</small>"
249         (markup_escape dev) (markup_escape name) in
250
251     let row = model#append () in
252     self#make_node row (Top (Volume dev)) None;
253     model#set ~row ~column:name_col markup
254
255   (* Add a top level Windows Registry node. *)
256   method private add_top_level_winreg name os rootkey remotefile =
257     let cachefile = tmpdir // string_of_int (unique ()) ^ ".hive" in
258
259     let markup =
260       sprintf "<b>%s</b>\n<small>from %s</small>"
261         (markup_escape rootkey) (markup_escape name) in
262
263     let row = model#append () in
264     self#make_node row
265       (TopWinReg (OS os, rootkey, remotefile, cachefile)) None;
266     model#set ~row ~column:name_col markup
267
268   (* Generic function to make an openable node to the tree. *)
269   method private make_node row content hiveh =
270     let hdata =
271       { state=NodeNotStarted; content=content; visited=false; hiveh=hiveh } in
272     self#store_hdata row hdata;
273
274     (* Create a placeholder "loading ..." row underneath this node so
275      * the user has something to expand.
276      *)
277     let placeholder = model#append ~parent:row () in
278     let hdata = { state=IsLeaf; content=Loading; visited=false; hiveh=None } in
279     self#store_hdata placeholder hdata;
280     model#set ~row:placeholder ~column:name_col "<i>Loading ...</i>";
281     ignore (self#connect#row_expanded ~callback:self#user_expand_row)
282
283   method private make_leaf row content hiveh =
284     let hdata = { state=IsLeaf; content=content; visited=false; hiveh=hiveh } in
285     self#store_hdata row hdata
286
287   (* This is called when the user expands a row. *)
288   method private user_expand_row row _ =
289     match self#get_hdata row with
290     | { state=NodeNotStarted; content=Top src } as hdata ->
291         (* User has opened a top level node that was not previously opened. *)
292
293         (* Mark this row as loading, so we don't try to open it again. *)
294         hdata.state <- NodeLoading;
295
296         (* Get a stable path for this row. *)
297         let path = model#get_path row in
298
299         Slave.read_directory ~fail:(self#when_read_directory_fail path)
300           src "/" (self#when_read_directory path)
301
302     | { state=NodeNotStarted; content=Directory direntry } as hdata ->
303         (* User has opened a filesystem directory not previously opened. *)
304
305         (* Mark this row as loading. *)
306         hdata.state <- NodeLoading;
307
308         (* Get a stable path for this row. *)
309         let path = model#get_path row in
310
311         let src, pathname = self#get_pathname row in
312
313         Slave.read_directory ~fail:(self#when_read_directory_fail path)
314           src pathname (self#when_read_directory path)
315
316     | { state=NodeNotStarted;
317         content=TopWinReg topdata } as hdata ->
318         (* User has opened a Windows Registry top level node
319          * not previously opened.
320          *)
321
322         (* Mark this row as loading. *)
323         hdata.state <- NodeLoading;
324
325         (* Get a stable path for this row. *)
326         let path = model#get_path row in
327
328         (* Since the user has opened this top level registry node for the
329          * first time, we now need to download the hive.
330          *)
331         self#get_registry_file ~fail:(self#when_downloaded_registry_fail path)
332           path topdata (self#when_downloaded_registry path)
333
334     | { state=NodeNotStarted; content=RegKey node } as hdata ->
335         (* User has opened a Windows Registry key node not previously opened. *)
336
337         (* Mark this row as loading. *)
338         hdata.state <- NodeLoading;
339
340         self#expand_hive_node row node
341
342     (* Ignore when a user opens a node which is loading or has been loaded. *)
343     | { state=(NodeLoading|IsNode) } -> ()
344
345     (* In some circumstances these can be nodes, eg. if we have added Info
346      * nodes below them.  Just ignore them if opened.
347      *)
348     | { content=(File _ | RegValue _) } | { state=IsLeaf } -> ()
349
350     (* Node should not exist in the tree. *)
351     | { state=NodeNotStarted; content=(Loading | ErrorMessage _ | Info _) } ->
352         assert false
353
354   (* This is the callback when the slave has read the directory for us. *)
355   method private when_read_directory path entries =
356     debug "when_read_directory";
357
358     let row = model#get_iter path in
359
360     (* Sort the entries by lexicographic ordering. *)
361     let cmp { dent_name = n1 } { dent_name = n2 } =
362       UTF8.compare n1 n2
363     in
364     let entries = List.sort ~cmp entries in
365
366     (* Add the entries. *)
367     List.iter (
368       fun direntry ->
369         let { dent_name = name; dent_stat = stat; dent_link = link } =
370           direntry in
371         let row = model#append ~parent:row () in
372         if is_directory stat.G.mode then
373           self#make_node row (Directory direntry) None
374         else
375           self#make_leaf row (File direntry) None;
376         model#set ~row ~column:name_col (markup_of_name direntry);
377         model#set ~row ~column:mode_col (markup_of_mode stat.G.mode);
378         model#set ~row ~column:size_col (markup_of_size stat.G.size);
379         model#set ~row ~column:date_col (markup_of_date stat.G.mtime);
380     ) entries;
381
382     (* Remove the placeholder "Loading" entry.  NB. Must be done AFTER
383      * adding the other entries, or else Gtk will unexpand the row.
384      *)
385     (try
386        let row = self#find_child_node_by_content row Loading in
387        ignore (model#remove row)
388      with Invalid_argument _ | Not_found -> ()
389     );
390
391     (* The original directory entry has now been loaded, so
392      * update its state.
393      *)
394     let hdata = self#get_hdata row in
395     hdata.state <- IsNode;
396     self#set_visited row
397
398   (* This is called instead of when_read_directory when the read directory
399    * (or mount etc) failed.  Convert the "Loading" entry into the
400    * error message.
401    *)
402   method private when_read_directory_fail path exn =
403     debug "when_read_directory_fail: %s" (Printexc.to_string exn);
404
405     match exn with
406     | G.Error msg ->
407         let row = model#get_iter path in
408         let row = model#iter_children ~nth:0 (Some row) in
409
410         let hdata =
411           { state=IsLeaf; content=ErrorMessage msg;
412             visited=false; hiveh=None } in
413         self#store_hdata row hdata;
414
415         model#set ~row ~column:name_col (markup_escape msg)
416
417     | exn ->
418         (* unexpected exception: re-raise it *)
419         raise exn
420
421   (* Called when the top level registry node has been opened and the
422    * hive file was downloaded to the cache file successfully.
423    *)
424   method private when_downloaded_registry path _ =
425     debug "when_downloaded_registry";
426     let row = model#get_iter path in
427     let hdata = self#get_hdata row in
428     let h = Option.get hdata.hiveh in
429
430     (* Continue as if expanding any other hive node. *)
431     let root = Hivex.root h in
432     self#expand_hive_node row root
433
434   (* Called instead of {!when_downloaded_registry} if the download failed. *)
435   method private when_downloaded_registry_fail path exn =
436     debug "when_downloaded_registry_fail: %s" (Printexc.to_string exn);
437
438     match exn with
439     | G.Error msg
440     | Hivex.Error (_, _, msg) ->
441         let row = model#get_iter path in
442         let row = model#iter_children ~nth:0 (Some row) in
443
444         let hdata =
445           { state=IsLeaf; content=ErrorMessage msg;
446             visited=false; hiveh=None } in
447         self#store_hdata row hdata;
448
449         model#set ~row ~column:name_col (markup_escape msg)
450
451     | exn ->
452         (* unexpected exception: re-raise it *)
453         raise exn
454
455   (* Expand a hive node. *)
456   method private expand_hive_node row node =
457     debug "expand_hive_node";
458     let hdata = self#get_hdata row in
459     let h = Option.get hdata.hiveh in
460
461     (* Read the hive entries (values, subkeys) at this node and add them
462      * to the tree.
463      *)
464     let values = Hivex.node_values h node in
465     let cmp v1 v2 =
466       UTF8.compare (Hivex.value_key h v1) (Hivex.value_key h v2)
467     in
468     Array.sort cmp values;
469     Array.iter (
470       fun value ->
471         let row = model#append ~parent:row () in
472         self#make_leaf row (RegValue value) (Some h);
473         model#set ~row ~column:name_col (markup_of_regvalue h value);
474         model#set ~row ~column:size_col (markup_of_regvaluesize h value);
475         model#set ~row ~column:date_col (markup_of_regvaluetype h value);
476     ) values;
477
478     let children = Hivex.node_children h node in
479     let cmp n1 n2 =
480       UTF8.compare (Hivex.node_name h n1) (Hivex.node_name h n2)
481     in
482     Array.sort cmp children;
483     Array.iter (
484       fun node ->
485         let row = model#append ~parent:row () in
486         self#make_node row (RegKey node) (Some h);
487         model#set ~row ~column:name_col (markup_of_regkey h node);
488     ) children;
489
490     (* Remove the placeholder "Loading" entry.  NB. Must be done AFTER
491      * adding the other entries, or else Gtk will unexpand the row.
492      *)
493     (try
494        let row = self#find_child_node_by_content row Loading in
495        ignore (model#remove row)
496      with Invalid_argument _ | Not_found -> ()
497     );
498
499     (* The original entry has now been loaded, so update its state. *)
500     hdata.state <- IsNode;
501     self#set_visited row
502
503   (* Return os(es) in the tree, if any.  The root directory of the
504    * tree looks like this:
505    *
506    *  \ Top (OS ...)   # usually only one, but there can be zero or > 1
507    *  \ Top (OS ...)
508    *  \ Top (Volume ...)
509    *  \ TopWinReg
510    *  \ TopWinReg
511    *
512    * This returns only the Top (OS ...) entries.  See also #add_top_level_os
513    * method.
514    *)
515   method oses =
516     match model#get_iter_first with
517     | None -> []
518     | Some row ->
519         let rec loop acc =
520           let acc =
521             match (self#get_hdata row).content with
522             | Top (OS os) -> os :: acc
523             | _ -> acc in
524           if model#iter_next row then
525             loop acc
526           else
527             List.rev acc
528         in
529         loop []
530
531   (* Signals. *)
532   method clear_tree : callback:(unit -> unit) -> GtkSignal.id =
533     clear_tree#connect ~after
534   method op_checksum_file = op_checksum_file#connect ~after
535   method op_copy_regvalue = op_copy_regvalue#connect ~after
536   method op_disk_usage = op_disk_usage#connect ~after
537   method op_download_as_reg = op_download_as_reg#connect ~after
538   method op_download_dir_find0 = op_download_dir_find0#connect ~after
539   method op_download_dir_tarball = op_download_dir_tarball#connect ~after
540   method op_download_file = op_download_file#connect ~after
541   method op_file_information = op_file_information#connect ~after
542   method op_inspection_dialog = op_inspection_dialog#connect ~after
543   method op_view_file = op_view_file#connect ~after
544
545   (* Handle mouse button press on the selected row.  This opens the
546    * pop-up context menu.
547    * http://scentric.net/tutorial/sec-selections-context-menus.html
548    *)
549   method private button_press ev =
550     let button = GdkEvent.Button.button ev in
551     let x = int_of_float (GdkEvent.Button.x ev) in
552     let y = int_of_float (GdkEvent.Button.y ev) in
553     let time = GdkEvent.Button.time ev in
554
555     (* Right button for opening the context menu. *)
556     if button = 3 then (
557 (*
558     (* If no row is selected, select the row under the mouse. *)
559     let paths =
560       let sel = view#selection in
561       if sel#count_selected_rows < 1 then (
562         match view#get_path_at_pos ~x ~y with
563         | None -> []
564         | Some (path, _, _, _) ->
565             sel#unselect_all ();
566             sel#select_path path;
567             [path]
568       ) else
569         sel#get_selected_rows (* actually returns paths *) in
570 *)
571       (* Select the row under the mouse. *)
572       let paths =
573         let sel = view#selection in
574         match view#get_path_at_pos ~x ~y with
575         | None -> []
576         | Some (path, _, _, _) ->
577             sel#unselect_all ();
578             sel#select_path path;
579             [path] in
580
581       (* Get the hdata for all the paths.  Filter out rows that it doesn't
582        * make sense to select.
583        *)
584       let paths =
585         List.filter_map (
586           fun path ->
587             let row = model#get_iter path in
588             let hdata = self#get_hdata row in
589             match hdata with
590             | { content=(Loading | ErrorMessage _ | Info _) } -> None
591             | { content=(Top _ | Directory _ | File _ |
592                              TopWinReg _ | RegKey _ | RegValue _ ) } ->
593                 Some (path, hdata)
594         ) paths in
595
596       (* Based on number of selected rows and what is selected, construct
597        * the context menu.
598        *)
599       (match self#make_context_menu paths with
600        | Some menu -> menu#popup ~button ~time
601        | None -> ()
602       );
603
604       (* Return true so no other handler will run. *)
605       true
606     )
607     (* We didn't handle this, defer to other handlers. *)
608     else false
609
610   method private make_context_menu paths =
611     let menu = GMenu.menu () in
612     let factory = new GMenu.factory menu in
613
614     let rec add_file_items path =
615       let item = factory#add_item "View ..." in
616       (match Config.opener with
617        | Some opener ->
618            ignore (item#connect#activate
619                      ~callback:(fun () -> op_view_file#call (path, opener)));
620        | None ->
621            item#misc#set_sensitive false
622       );
623       let item = factory#add_item "File information" in
624       ignore (item#connect#activate
625                 ~callback:(fun () -> op_file_information#call path));
626       let item = factory#add_item "MD5 checksum" in
627       ignore (item#connect#activate
628                 ~callback:(fun () -> op_checksum_file#call (path, "md5")));
629       let item = factory#add_item "SHA1 checksum" in
630       ignore (item#connect#activate
631                 ~callback:(fun () -> op_checksum_file#call (path, "sha1")));
632       ignore (factory#add_separator ());
633       let item = factory#add_item "Download ..." in
634       ignore (item#connect#activate
635                 ~callback:(fun () -> op_download_file#call path));
636
637     and add_directory_items path =
638       let item = factory#add_item "Directory information" in
639       item#misc#set_sensitive false;
640       let item = factory#add_item "Calculate disk usage" in
641       ignore (item#connect#activate
642                 ~callback:(fun () -> op_disk_usage#call path));
643       ignore (factory#add_separator ());
644       let item = factory#add_item "Download ..." in
645       item#misc#set_sensitive false;
646       let item = factory#add_item "Download as .tar ..." in
647       ignore (item#connect#activate
648                 ~callback:(fun () -> op_download_dir_tarball#call (Tar, path)));
649       let item = factory#add_item "Download as .tar.gz ..." in
650       ignore (item#connect#activate
651                 ~callback:(fun () -> op_download_dir_tarball#call (TGZ, path)));
652       let item = factory#add_item "Download as .tar.xz ..." in
653       ignore (item#connect#activate
654                 ~callback:(fun () -> op_download_dir_tarball#call (TXZ, path)));
655       let item = factory#add_item "Download list of filenames ..." in
656       ignore (item#connect#activate
657                 ~callback:(fun () -> op_download_dir_find0#call path));
658
659     and add_top_os_items os path =
660       let item = factory#add_item "Operating system information ..." in
661       ignore (item#connect#activate
662                 ~callback:(fun () -> op_inspection_dialog#call os));
663       ignore (factory#add_separator ());
664       add_top_volume_items path
665
666     and add_top_volume_items path =
667       let item = factory#add_item "Filesystem used & free" in
668       item#misc#set_sensitive false;
669       let item = factory#add_item "Block device information" in
670       item#misc#set_sensitive false;
671       ignore (factory#add_separator ());
672       add_directory_items path
673
674     and add_topwinreg_items path =
675       let item = factory#add_item "Download hive file ..." in
676       item#misc#set_sensitive false;
677       ignore (factory#add_separator ());
678       add_regkey_items path
679
680     and add_regkey_items path =
681       let item = factory#add_item "Download as .reg file ..." in
682       (match Config.hivexregedit with
683        | Some hivexregedit ->
684            ignore (item#connect#activate
685                      ~callback:(fun () ->
686                                 op_download_as_reg#call (path, hivexregedit)));
687        | None ->
688            item#misc#set_sensitive false
689       )
690
691     and add_regvalue_items path =
692       let item = factory#add_item "Copy value to clipboard" in
693       ignore (item#connect#activate
694                 ~callback:(fun () -> op_copy_regvalue#call path));
695
696     in
697
698     let has_menu =
699       match paths with
700       | [] -> false
701
702       (* single selection *)
703       | [path, { content=Top (OS os)} ] ->  (* top level operating system *)
704           add_top_os_items os path; true
705
706       | [path, { content=Top (Volume dev) }] -> (* top level volume *)
707           add_top_volume_items path; true
708
709       | [path, { content=Directory _ }] -> (* directory *)
710           add_directory_items path; true
711
712       | [path, { content=File _ }] ->      (* file *)
713           add_file_items path; true
714
715       | [path, { content=TopWinReg _ }] -> (* top level registry node *)
716           add_topwinreg_items path; true
717
718       | [path, { content=RegKey _ }] ->    (* registry node *)
719           add_regkey_items path; true
720
721       | [path, { content=RegValue _ }] ->  (* registry key/value pair *)
722           add_regvalue_items path; true
723
724       | [_, { content=(Loading|ErrorMessage _|Info _) }] -> false
725
726       | _::_::_ ->
727           (* At the moment multiple selection is disabled.  When/if we
728            * enable it we should do something intelligent here. XXX
729            *)
730           false in
731     if has_menu then Some menu else None
732
733   (* Store hdata into a row. *)
734   method private store_hdata row hdata =
735     let index = unique () in
736     Hashtbl.add hash index hdata;
737     model#set ~row ~column:index_col index
738
739   (* Retrieve previously stored hdata from a row. *)
740   method private get_hdata row =
741     let index = model#get ~row ~column:index_col in
742     try Hashtbl.find hash index
743     with Not_found -> assert false
744
745   (* [find_child_node_by_content row content] searches the direct
746      children of [row] looking for one which exactly matches
747      [hdata.content] and returns that child.  If no child found,
748      raises [Not_found]. *)
749   method private find_child_node_by_content row c =
750     let rec loop row =
751       if (self#get_hdata row).content = c then
752         row
753       else if model#iter_next row then
754         loop row
755       else
756         raise Not_found
757     in
758
759     if not (model#iter_has_child row) then
760       raise Not_found;
761
762     let first_child = model#iter_children (Some row) in
763     loop first_child
764
765   (* Search up to the top of the tree so we know if this directory
766    * comes from an OS or a volume, and the full path to here.
767    *
768    * The path up the tree will always look something like:
769    *     Top
770    *       \_ Directory
771    *            \_ Directory
772    *                 \_ Loading    <--- you are here
773    *
774    * Note this function cannot be called on registry keys.  See
775    * {!get_registry_path} for that.
776    *)
777   method get_pathname row =
778     let hdata = self#get_hdata row in
779     let parent = model#iter_parent row in
780
781     match hdata, parent with
782     | { state=IsLeaf; content=(Loading|ErrorMessage _|Info _) }, Some parent ->
783         self#get_pathname parent
784     | { state=IsLeaf; content=(Loading|ErrorMessage _|Info _) }, None ->
785         assert false
786     | { content=Directory { dent_name = name }}, Some parent
787     | { content=File { dent_name = name }}, Some parent ->
788         let src, parent_name = self#get_pathname parent in
789         let path =
790           if parent_name = "/" then "/" ^ name
791           else parent_name ^ "/" ^ name in
792         src, path
793     | { content=Top src }, _ -> src, "/"
794     | { content=Directory _ }, None -> assert false
795     | { content=File _ }, None -> assert false
796     | { content=Loading }, _ -> assert false
797     | { content=ErrorMessage _ }, _ -> assert false
798     | { content=Info _ }, _ -> assert false
799     | { content=TopWinReg _ }, _ -> assert false
800     | { content=RegKey _ }, _ -> assert false
801     | { content=RegValue _ }, _ -> assert false
802
803   (* Search up to the top of the tree from a registry key.
804    *
805    * The path up the tree will always look something like:
806    *     TopWinReg
807    *       \_ RegKey
808    *            \_ RegKey          <--- you are here
809    *                 \_ Loading    <--- or here
810    *
811    * Note this function cannot be called on ordinary paths.  Use
812    * {!get_pathname} for that.
813    *)
814   method get_registry_path row =
815     let hdata = self#get_hdata row in
816     let parent = model#iter_parent row in
817
818     match hdata, parent with
819     | { state=IsLeaf; content=(Loading|ErrorMessage _|Info _) }, Some parent ->
820         self#get_registry_path parent
821     | { state=IsLeaf; content=(Loading|ErrorMessage _|Info _) }, None ->
822         assert false
823     | { content=RegKey node; hiveh = Some h }, Some parent ->
824         let top, path = self#get_registry_path parent in
825         let path = Hivex.node_name h node :: path in
826         top, path
827     | { content=TopWinReg (a,b,c,d) }, None -> (a,b,c,d), []
828     | { content=TopWinReg _ }, _ -> assert false
829     | { content=RegKey _}, _ -> assert false
830     | { content=Top _ }, _ -> assert false
831     | { content=Directory _ }, _ -> assert false
832     | { content=File _ }, _ -> assert false
833     | { content=Loading }, _ -> assert false
834     | { content=ErrorMessage _ }, _ -> assert false
835     | { content=Info _ }, _ -> assert false
836     | { content=RegValue _ }, _ -> assert false
837
838   method get_registry_value row =
839     let hdata = self#get_hdata row in
840     match hdata with
841     | { content=RegValue value; hiveh = Some h } ->
842         Hivex.value_value h value
843     | _ -> assert false (* not a registry value *)
844
845   (* This is called whenever we need the registry cache file and we
846      can't be sure that it has already been downloaded. *)
847   method get_registry_file ?fail path (src, _, remotefile, cachefile) cb =
848     let row = model#get_iter path in
849     let top =
850       let rec loop row =
851         match model#iter_parent row with
852         | None -> row
853         | Some parent -> loop parent
854       in
855       loop row in
856
857     Slave.download_file_if_not_exist ?fail src remotefile cachefile
858       (self#when_got_registry_file ?fail top cb)
859
860   method private when_got_registry_file ?fail top cb () =
861     debug "when_got_registry_file";
862     let hdata = self#get_hdata top in
863
864     match hdata with
865     | { hiveh=Some _; content=TopWinReg (_, _, _, cachefile) } ->
866         (* Hive handle already opened. *)
867         cb cachefile
868
869     | { hiveh=None; content=TopWinReg (src, rootkey, remotefile, cachefile) } ->
870         (* Hive handle not opened, open it and save it in the handle. *)
871         (try
872            let flags = if verbose () then [ Hivex.OPEN_VERBOSE ] else [] in
873            let h = Hivex.open_file cachefile flags in
874            hdata.hiveh <- Some h;
875            cb cachefile
876          with
877            Hivex.Error _ as exn ->
878              match fail with
879              | Some fail -> fail exn
880              | None -> raise exn
881         )
882
883     | _ -> assert false
884
885   (* This is a bit of a hack.  Ideally just setting 'visited' would
886    * darken the colour when the cell was re-rendered.  However that would
887    * mean we couldn't store other stuff in the name column.  Therefore,
888    * repopulate the name column.
889    *)
890   method set_visited row =
891     let hdata = self#get_hdata row in
892     if hdata.visited = false then (
893       hdata.visited <- true;
894       match hdata.content with
895       | Directory direntry | File direntry ->
896           debug "set_visited %s" direntry.dent_name;
897           model#set ~row ~column:name_col
898             (markup_of_name ~visited:true direntry)
899       | RegKey node ->
900           debug "set_visited RegKey";
901           let h = Option.get hdata.hiveh in
902           model#set ~row ~column:name_col
903             (markup_of_regkey ~visited:true h node)
904       | RegValue value ->
905           debug "set_visited RegValue";
906           let h = Option.get hdata.hiveh in
907           model#set ~row ~column:name_col
908             (markup_of_regvalue ~visited:true h value)
909       | Loading | ErrorMessage _ | Info _ | Top _ | TopWinReg _ -> ()
910     )
911
912   method has_child_info_node path info_text =
913     let row = model#get_iter path in
914     let content = Info info_text in
915     try ignore (self#find_child_node_by_content row content); true
916     with Not_found -> false
917
918   method set_child_info_node path info_text text =
919     self#expand_row path;
920     let row = model#get_iter path in
921     let content = Info info_text in
922     let row =
923       try self#find_child_node_by_content row content
924       with Not_found -> model#insert ~parent:row 0 in
925     let hdata = { state=IsLeaf; content=content; visited=false; hiveh=None } in
926     self#store_hdata row hdata;
927     model#set ~row ~column:name_col text
928
929 end