Block free/used for NTFS working
[virt-df.git] / lib / diskimage_impl.ml
1 (* Diskimage library for reading disk images.
2    (C) Copyright 2007-2008 Richard W.M. Jones, Red Hat Inc.
3    http://libvirt.org/
4
5    This program is free software; you can redistribute it and/or modify
6    it under the terms of the GNU General Public License as published by
7    the Free Software Foundation; either version 2 of the License, or
8    (at your option) any later version.
9
10    This program is distributed in the hope that it will be useful,
11    but WITHOUT ANY WARRANTY; without even the implied warranty of
12    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13    GNU General Public License for more details.
14
15    You should have received a copy of the GNU General Public License
16    along with this program; if not, write to the Free Software
17    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
18  *)
19
20 open ExtList
21 open Printf
22 open Unix
23
24 open Int63.Operators
25
26 let debug = ref false
27
28 (* Use as the natural block size for disk images, but really we should
29  * use the 'blockdev -getbsz' command to find the real block size.
30  *)
31 let disk_block_size = ~^512
32
33 class virtual device =
34 object (self)
35   method virtual size : int63
36   method virtual name : string
37   method virtual blocksize : int63
38   method virtual map_block : int63 -> (device * int63) list
39   method virtual contiguous : Int63.t -> Int63.t
40
41   (* Block-based read.  Inefficient so normally overridden in subclasses. *)
42   method read offset len =
43     if offset < ~^0 || len < ~^0 then
44       invalid_arg "device: read: negative offset or length";
45
46     let blocksize = self#blocksize in
47
48     (* Break the request into blocks.
49      * Find the first and last blocks of this request.
50      *)
51     let first_blk = offset /^ blocksize in
52     let offset_in_first_blk = offset -^ first_blk *^ blocksize in
53     let last_blk = (offset +^ len -^ ~^1) /^ blocksize in
54
55     (* Buffer for the result. *)
56     let buf = Buffer.create (Int63.to_int len) in
57
58     let not_mapped_error () = invalid_arg "device: read: block not mapped" in
59
60     (* Copy the first block (partial). *)
61     (match self#map_block first_blk with
62      | [] -> not_mapped_error ()
63      | (dev, base) :: _ ->
64          let len =
65            min len (blocksize -^ offset_in_first_blk) in
66          let str = dev#read (base +^ offset_in_first_blk) len in
67          Buffer.add_string buf str
68     );
69
70     (* Copy the middle blocks. *)
71     let rec loop blk =
72       if blk < last_blk then (
73         (match self#map_block blk with
74          | [] -> not_mapped_error ()
75          | (dev, base) :: _ ->
76              let str = dev#read ~^0 self#blocksize in
77              Buffer.add_string buf str
78         );
79         loop (Int63.succ blk)
80       )
81     in
82     loop (Int63.succ first_blk);
83
84     (* Copy the last block (partial). *)
85     if first_blk < last_blk then (
86       match self#map_block last_blk with
87       | [] -> not_mapped_error ()
88       | (dev, base) :: _ ->
89           let len = (offset +^ len) -^ last_blk *^ blocksize in
90           let str = dev#read ~^0 len in
91           Buffer.add_string buf str
92     );
93
94     assert (Int63.to_int len = Buffer.length buf);
95     Buffer.contents buf
96
97   (* Helper method to read a chunk of data into a bitstring. *)
98   method read_bitstring offset len =
99     let str = self#read offset len in
100     (str, 0, String.length str lsl 3)
101 end
102
103 (* A concrete device which just direct-maps a file or /dev device. *)
104 class block_device filename blocksize =
105   let fd = openfile filename [ O_RDONLY ] 0 in
106   let size = Int63.of_int64 (LargeFile.fstat fd).LargeFile.st_size in
107 object (self)
108   inherit device
109   method read offset len =
110     let offset = Int63.to_int64 offset in
111     let len = Int63.to_int len in
112     ignore (LargeFile.lseek fd offset SEEK_SET);
113     let str = String.make len '\000' in
114     ignore (read fd str 0 len);
115     str
116   method size = size
117   method name = filename
118   method blocksize = blocksize
119   method map_block _ = []
120   method contiguous offset =
121     size -^ offset
122   method close () = close fd
123 end
124
125 (* A linear offset/size from an underlying device. *)
126 class offset_device name start size blocksize (dev : device) =
127 object
128   inherit device
129   method name = name
130   method size = size
131   method read offset len =
132     if offset < ~^0 || len < ~^0 || offset +^ len > size then
133       invalid_arg (
134         sprintf "%s: tried to read outside device boundaries (%s/%s/%s)"
135           name (Int63.to_string offset) (Int63.to_string len)
136           (Int63.to_string size)
137       );
138     dev#read (start+^offset) len
139   method blocksize = blocksize
140   method map_block i = [dev, i *^ blocksize +^ start]
141   method contiguous offset =
142     size -^ offset
143 end
144
145 (* A device with just a modified block size. *)
146 class blocksize_overlay new_blocksize (dev : device) =
147 object
148   inherit device
149   method name = dev#name
150   method size = dev#size
151   method read = dev#read
152   method blocksize = new_blocksize
153   method map_block new_blk =
154     let orig_blk = new_blk *^ new_blocksize /^ dev#blocksize in
155     dev#map_block orig_blk
156   method contiguous offset = dev#size -^ offset
157 end
158
159 (* The null device.  Any attempt to read generates an error. *)
160 let null_device : device =
161 object
162   inherit device
163   method read _ _ = assert false
164   method size = ~^0
165   method name = "null"
166   method blocksize = ~^1
167   method map_block _ = assert false
168   method contiguous _ = ~^0
169 end
170
171 type machine = {
172   m_name : string;                      (* Machine name. *)
173   m_disks : disk list;                  (* Machine disks. *)
174   m_lv_filesystems :
175     (lv * filesystem) list;             (* Machine LV filesystems. *)
176 }
177 and disk = {
178   d_name : string;                      (* Device name (eg "hda") *)
179
180   (* About the device itself. *)
181   d_dev : block_device;                 (* Disk device. *)
182   d_content : disk_content;             (* What's on it. *)
183 }
184 and disk_content =
185   [ `Unknown                            (* Not probed or unknown. *)
186   | `Partitions of partitions           (* Contains partitions. *)
187   | `Filesystem of filesystem           (* Contains a filesystem directly. *)
188   | `PhysicalVolume of pv               (* Contains an LVM PV. *)
189   ]
190
191 (* Partitions. *)
192
193 and partitions = {
194   parts_cb : partitioner_callbacks;     (* Partitioning scheme. *)
195   parts_dev : device;                   (* Partitions (whole) device. *)
196   parts : partition list                (* Partitions. *)
197 }
198 and partition = {
199   part_status : partition_status;       (* Bootable, etc. *)
200   part_type : int;                      (* Partition filesystem type. *)
201   part_dev : device;                    (* Partition device. *)
202   part_content : partition_content;     (* What's on it. *)
203 }
204 and partition_status = Bootable | Nonbootable | Malformed | NullEntry
205 and partition_content =
206   [ `Unknown                            (* Not probed or unknown. *)
207   | `Filesystem of filesystem           (* Filesystem. *)
208   | `PhysicalVolume of pv               (* Contains an LVM PV. *)
209   ]
210
211 (* Filesystems (also swap devices). *)
212 and filesystem = {
213   fs_cb : filesystem_callbacks;         (* Filesystem. *)
214   fs_dev : device;                      (* Device containing the filesystem. *)
215   fs_blocksize : int63;                 (* Block size (bytes). *)
216   fs_blocks_total : int63;              (* Total blocks. *)
217   fs_is_swap : bool;                    (* If swap, following not valid. *)
218   fs_blocks_reserved : int63;           (* Blocks reserved for super-user. *)
219   fs_blocks_avail : int63;              (* Blocks free (available). *)
220   fs_blocks_used : int63;               (* Blocks in use. *)
221   fs_inodes_total : int63;              (* Total inodes. *)
222   fs_inodes_reserved : int63;           (* Inodes reserved for super-user. *)
223   fs_inodes_avail : int63;              (* Inodes free (available). *)
224   fs_inodes_used : int63;               (* Inodes in use. *)
225 }
226
227 (* Physical volumes. *)
228 and pv = {
229   pv_cb : lvm_callbacks;                (* The LVM plug-in. *)
230   pv_dev : device;                      (* Device covering whole PV. *)
231   pv_uuid : string;                     (* UUID. *)
232 }
233
234 (* Logical volumes. *)
235 and lv = {
236   lv_dev : device;                      (* Logical volume device. *)
237 }
238
239 (* Tables of callbacks. *)
240 and partitioner_probe = device -> partitions
241
242 and partitioner_callbacks = {
243   parts_cb_uq : int;
244   parts_cb_name : string;
245   parts_cb_offset_is_free : partitions -> Int63.t -> bool;
246 }
247
248 and filesystem_probe = device -> filesystem
249
250 and filesystem_callbacks = {
251   fs_cb_uq : int;
252   fs_cb_name : string;
253   fs_cb_printable_name : string;
254   fs_cb_offset_is_free : filesystem -> Int63.t -> bool;
255 }
256
257 and lvm_probe = device -> pv
258
259 and lvm_callbacks = {
260   lvm_cb_uq : int;
261   lvm_cb_name : string;
262   lvm_cb_list_lvs : pv list -> lv list;
263   lvm_cb_offset_is_free : pv -> Int63.t -> bool;
264 }
265
266 let name_of_filesystem { fs_cb = { fs_cb_printable_name = name } } = name
267
268 (*----------------------------------------------------------------------*)
269 (* Helper functions. *)
270
271 (* Convert a UUID (containing '-' chars) to canonical form. *)
272 let canonical_uuid uuid =
273   let uuid' = String.make 32 ' ' in
274   let j = ref 0 in
275   for i = 0 to String.length uuid - 1 do
276     if !j >= 32 then invalid_arg "canonical_uuid";
277     let c = uuid.[i] in
278     if c <> '-' then ( uuid'.[!j] <- c; incr j )
279   done;
280   if !j <> 32 then invalid_arg "canonical_uuid";
281   uuid'
282
283 (* This version by Isaac Trotts. *)
284 let group_by ?(cmp = Pervasives.compare) ls =
285   let ls' =
286     List.fold_left
287       (fun acc (day1, x1) ->
288          match acc with
289              [] -> [day1, [x1]]
290            | (day2, ls2) :: acctl ->
291                if cmp day1 day2 = 0
292                then (day1, x1 :: ls2) :: acctl
293                else (day1, [x1]) :: acc)
294       []
295       ls
296   in
297   let ls' = List.rev ls' in
298   List.map (fun (x, xs) -> x, List.rev xs) ls'
299
300 let rec uniq ?(cmp = Pervasives.compare) = function
301   | [] -> []
302   | [x] -> [x]
303   | x :: y :: xs when cmp x y = 0 ->
304       uniq (x :: xs)
305   | x :: y :: xs ->
306       x :: uniq (y :: xs)
307
308 let sort_uniq ?cmp xs =
309   let xs = ExtList.List.sort ?cmp xs in
310   let xs = uniq ?cmp xs in
311   xs
312
313 let rec range a b =
314   if a < b then a :: range (a+1) b
315   else []
316
317 (*----------------------------------------------------------------------*)
318 (* The plug-ins. *)
319
320 let partitioners = ref []
321 let filesystems = ref []
322 let lvms = ref []
323
324 let register_plugin ?partitioner ?filesystem ?lvm id =
325   (match partitioner with
326    | None -> ()
327    | Some probe -> partitioners := !partitioners @ [id, probe]
328   );
329   (match filesystem with
330    | None -> ()
331    | Some probe -> filesystems := !filesystems @ [id, probe]
332   );
333   (match lvm with
334    | None -> ()
335    | Some probe -> lvms := !lvms @ [id, probe]
336   )
337
338 (* Probe a device for partitions.  Returns [Some parts] or [None]. *)
339 let probe_for_partitions dev =
340   if !debug then eprintf "probing for partitions on %s ...\n%!" dev#name;
341   let rec loop = function
342     | [] -> None
343     | (_, probe) :: rest ->
344         try Some (probe dev)
345         with Not_found -> loop rest
346   in
347   let r = loop !partitioners in
348   if !debug then (
349     match r with
350     | None -> eprintf "no partitions found on %s\n%!" dev#name
351     | Some { parts_cb = { parts_cb_name = name }; parts = parts } ->
352         eprintf "found %d %s partitions on %s\n"
353           (List.length parts) name dev#name
354   );
355   r
356
357 (* Probe a device for a filesystem.  Returns [Some fs] or [None]. *)
358 let probe_for_filesystem dev =
359   if !debug then eprintf "probing for a filesystem on %s ...\n%!" dev#name;
360   let rec loop = function
361     | [] -> None
362     | (_, probe) :: rest ->
363         try Some (probe dev)
364         with Not_found -> loop rest
365   in
366   let r = loop !filesystems in
367   if !debug then (
368     match r with
369     | None -> eprintf "no filesystem found on %s\n%!" dev#name
370     | Some fs ->
371         eprintf "found a filesystem on %s:\n" dev#name;
372         eprintf "\t%s\n%!" fs.fs_cb.fs_cb_name
373   );
374   r
375
376 (* Probe a device for a PV.  Returns [Some pv] or [None]. *)
377 let probe_for_pv dev =
378   if !debug then eprintf "probing if %s is a PV ...\n%!" dev#name;
379   let rec loop = function
380     | [] -> None
381     | (_, probe) :: rest ->
382         try Some (probe dev)
383         with Not_found -> loop rest
384   in
385   let r = loop !lvms in
386   if !debug then (
387     match r with
388     | None -> eprintf "no PV found on %s\n%!" dev#name
389     | Some { pv_cb = { lvm_cb_name = name } } ->
390         eprintf "%s contains a %s PV\n%!" dev#name name
391   );
392   r
393
394 (* This allows plug-ins to attach their own private data to
395  * the normal plug-in structures (partitions, filesystem, pv, etc.)
396  *)
397 let private_data_functions get_key =
398   let h = Hashtbl.create 13 in
399   (fun struc data ->
400      Hashtbl.replace h (get_key struc) data),
401   (fun struc ->
402      try Hashtbl.find h (get_key struc)
403      with Not_found -> assert false (* internal error in the plug-in *))
404
405 (*----------------------------------------------------------------------*)
406 (* Create machine description. *)
407 let open_machine name disks =
408   let disks = List.map (
409     fun (name, path) ->
410       let dev = new block_device path disk_block_size (* XXX *) in
411       { d_name = name; d_dev = dev; d_content = `Unknown }
412   ) disks in
413   { m_name = name; m_disks = disks; m_lv_filesystems = [] }
414
415 let close_machine { m_disks = m_disks } =
416   (* Only close the disks, assume all other devices are derived from them. *)
417   List.iter (fun { d_dev = d_dev } -> d_dev#close ()) m_disks
418
419 (* Main scanning function for filesystems. *)
420 let scan_machine ({ m_disks = m_disks } as machine) =
421   let m_disks = List.map (
422     fun ({ d_dev = dev } as disk) ->
423       let dev = (dev :> device) in
424       (* See if it is partitioned first. *)
425       let parts = probe_for_partitions dev in
426       match parts with
427       | Some parts ->
428           { disk with d_content = `Partitions parts }
429       | None ->
430           (* Not partitioned.  Does it contain a filesystem? *)
431           let fs = probe_for_filesystem dev in
432           match fs with
433           | Some fs ->
434               { disk with d_content = `Filesystem fs }
435           | None ->
436               (* Not partitioned, no filesystem, is it a PV? *)
437               let pv = probe_for_pv dev in
438               match pv with
439               | Some pv ->
440                   { disk with d_content = `PhysicalVolume pv }
441               | None ->
442                   disk (* Spare/unknown. *)
443   ) m_disks in
444
445   (* Now we have either detected partitions or a filesystem on each
446    * physical device (or perhaps neither).  See what is on those
447    * partitions.
448    *)
449   let m_disks = List.map (
450     function
451     | ({ d_dev = dev; d_content = `Partitions parts } as disk) ->
452         let ps = List.map (
453           fun p ->
454             if p.part_status = Bootable || p.part_status = Nonbootable then (
455               let fs = probe_for_filesystem p.part_dev in
456               match fs with
457               | Some fs ->
458                   { p with part_content = `Filesystem fs }
459               | None ->
460                   (* Is it a PV? *)
461                   let pv = probe_for_pv p.part_dev in
462                   match pv with
463                   | Some lvm_name ->
464                       { p with part_content = `PhysicalVolume lvm_name }
465                   | None ->
466                       p (* Spare/unknown. *)
467             ) else p
468         ) parts.parts in
469         let parts = { parts with parts = ps } in
470         { disk with d_content = `Partitions parts }
471     | disk -> disk
472   ) m_disks in
473
474   (* LVM filesystem detection
475    *
476    * Look for all disks/partitions which have been identified as PVs
477    * and pass those back to the respective LVM plugin for LV detection.
478    *
479    * (Note - a two-stage process because an LV can be spread over
480    * several PVs, so we have to detect all PVs belonging to a
481    * domain first).
482    *
483    * XXX To deal with RAID (ie. md devices) we will need to loop
484    * around here because RAID is like LVM except that they normally
485    * present as block devices which can be used by LVM.
486    *)
487   (* First: LV detection.
488    * Find all physical volumes, can be disks or partitions.
489    *)
490   let pvs_on_disks = List.filter_map (
491     function
492     | { d_content = `PhysicalVolume pv } -> Some pv
493     | _ -> None
494   ) m_disks in
495   let pvs_on_partitions = List.map (
496     function
497     | { d_content = `Partitions { parts = parts } } ->
498         List.filter_map (
499           function
500           | { part_content = `PhysicalVolume pv } -> Some pv
501           | _ -> None
502         ) parts
503     | _ -> []
504   ) m_disks in
505   let lvs = List.concat (pvs_on_disks :: pvs_on_partitions) in
506
507   (* Second: filesystem on LV detection.
508    * Group the LVs by LVM plug-in ID.
509    *)
510   let lvs =
511     List.map (fun ({pv_cb = {lvm_cb_name = name}} as pv) -> name, pv) lvs in
512   let lvs = List.sort lvs in
513   let lvs = group_by lvs in
514
515   let lvs = List.map (fun (name, pvs) ->
516                         let pv = List.hd pvs in
517                         pv.pv_cb.lvm_cb_list_lvs pvs) lvs in
518   let lvs = List.concat lvs in
519
520   (* lvs is a list of potential LV devices.  Now run them through the
521    * probes to see if any contain filesystems.
522    *)
523   let filesystems =
524     List.filter_map (
525       fun ({ lv_dev = dev } as lv) ->
526         match probe_for_filesystem dev with
527         | Some fs -> Some (lv, fs)
528         | None -> None
529     ) lvs in
530
531   { machine with
532       m_disks = m_disks;
533       m_lv_filesystems = filesystems }
534
535 (*----------------------------------------------------------------------*)
536
537 (* We describe the ownership of each part of the disk using a
538  * segment tree. http://en.wikipedia.org/wiki/Segment_tree
539  *
540  * Note that each part can (and usually is) owned multiple times
541  * (eg. by a filesystem and by the partition that the filesystem
542  * lies inside).  Also, the segment tree is effectively read-only.
543  * We build it up as a final step given the flat list of segments
544  * identified by the algorithm in 'iter_over_machine'.
545  *)
546
547 (* General binary tree type.  Data 'a is stored in the leaves and 'b
548  * is stored in the nodes.
549  *)
550 type ('a,'b) binary_tree =
551   | Leaf of 'a
552   | Node of ('a,'b) binary_tree * 'b * ('a,'b) binary_tree
553
554 (* This prints out the binary tree in graphviz dot format. *)
555 let print_binary_tree leaf_printer node_printer tree =
556   (* Assign a unique, fixed label to each node. *)
557   let label =
558     let i = ref 0 in
559     let hash = Hashtbl.create 13 in
560     fun node ->
561       try Hashtbl.find hash node
562       with Not_found ->
563         let i = incr i; !i in
564         let label = "n" ^ string_of_int i in
565         Hashtbl.add hash node label;
566         label
567   in
568   (* Recursively generate the graphviz file. *)
569   let rec print = function
570     | (Leaf a as leaf) ->
571         eprintf "  %s [shape=box, label=\"%s\"];\n"
572           (label leaf) (leaf_printer a)
573     | (Node (left,b,right) as node) ->
574         eprintf "  %s [label=\"%s\"];\n"
575           (label node) (node_printer b);
576         eprintf "  %s -> %s [tailport=sw];\n" (label node) (label left);
577         eprintf "  %s -> %s [tailport=se];\n" (label node) (label right);
578         print left;
579         print right;
580   in
581   eprintf "/* Use 'dot -Tpng foo.dot > foo.png' to convert to a png file. */\n";
582   eprintf "digraph G {\n";
583   print tree;
584   eprintf "}\n%!";
585
586 type owner =
587     [ `Filesystem of filesystem
588     | `Partitions of partitions
589     | `PhysicalVolume of pv ]
590
591 (* A segment describes the owner of a range of disk addresses. *)
592 type segment = owner * int63            (* owner, owner offset *)
593
594 type interval = int63 * int63           (* start point, end point (bytes) *)
595
596 (* The special segment tree structure that we construct in create_ownership. *)
597 type segment_tree =
598     (interval * segment list, interval * segment list) binary_tree
599
600 type ownership =
601     (device *                           (* block_device (disk) *)
602        segment_tree) list               (* segment tree for this disk *)
603
604 (* List of owned segments before we build the segment tree. *)
605 type ownership_list =
606     (device *                           (* block_device (disk) *)
607        (int63 * int63 *                 (* disk offset, size of segment *)
608           owner * int63                 (* owner, owner offset *)
609        )
610     ) list
611
612 (* Ownership tables. *)
613 let create_ownership machine =
614   (* Iterate over all the things which can claim ownership of a
615    * disk block (filesystems, partitions, PVs).
616    *)
617   let rec iter_over_machine
618       ({m_disks = disks; m_lv_filesystems = lv_filesystems} as machine) =
619
620     (* No segments to begin with. *)
621     let ownership = [] in
622
623     (* Iterate over disks. *)
624     let ownership =
625       List.fold_left (
626         fun ownership ->
627           function
628           | { d_content = (`Filesystem fs as owner) } ->
629               iter_over_filesystem machine ownership fs owner
630           | { d_content = (`Partitions parts as owner) } ->
631               iter_over_partitions machine ownership parts owner
632           | { d_content = (`PhysicalVolume pv as owner) } ->
633               iter_over_pv machine ownership pv owner
634           | { d_content = `Unknown } -> ownership
635       ) ownership disks in
636
637     (* Iterate over LV filesystems. *)
638     let ownership =
639       List.fold_left (
640         fun ownership (lv, fs) ->
641           let owner = `Filesystem fs in
642           iter_over_filesystem machine ownership fs owner
643       ) ownership lv_filesystems in
644
645     ownership
646
647   (* Iterate over the blocks in a single filesystem. *)
648   and iter_over_filesystem machine ownership {fs_dev = dev} owner =
649     iter_over_device machine ownership dev owner
650
651   (* Iterate over the blocks in a set of partitions, then
652    * iterate over the contents of the partitions.
653    *)
654   and iter_over_partitions machine ownership
655       {parts = parts; parts_dev = parts_dev} owner =
656     let ownership = iter_over_device machine ownership parts_dev owner in
657
658     let ownership =
659       List.fold_left (
660         fun ownership ->
661           function
662           | { part_content = (`Filesystem fs as owner) } ->
663               iter_over_filesystem machine ownership fs owner
664           | { part_content = (`PhysicalVolume pv as owner) } ->
665               iter_over_pv machine ownership pv owner
666           | { part_content = `Unknown } -> ownership
667       ) ownership parts in
668
669     ownership
670
671   (* Iterate over the blocks in a PV. *)
672   and iter_over_pv machine ownership {pv_dev = dev} owner =
673     iter_over_device machine ownership dev owner
674
675   (* Iterate over the blocks in a device, assigning ownership to 'owner'
676    *
677    * In reality (1): There can be several owners for each block, so we
678    * incrementally add ownership to the ownership_list (which eventually
679    * will be turned into a segment tree).
680    * In reality (2): Iterating over blocks would take ages and result
681    * in a very inefficient ownership representation.  Instead we look
682    * at minimum contiguous extents.
683    *)
684   and iter_over_device { m_disks = disks } ownership dev owner =
685     let size = dev#size in
686     let disks = List.map (fun {d_dev = dev} -> (dev :> device)) disks in
687
688     let rec loop ownership offset =
689       if offset < size then (
690         let devs, extent = get_next_extent disks dev offset in
691         if devs = [] then
692           eprintf "warning: no device found under %s\n"
693             (string_of_owner owner);
694         let ownership =
695           List.fold_left (
696             fun ownership (disk, disk_offset) ->
697               let elem = disk, (disk_offset, extent, owner, offset) in
698               elem :: ownership
699           ) ownership devs in
700         loop ownership (offset +^ extent)
701       )
702       else ownership
703     in
704     loop ownership ~^0
705
706   (* Return the length of the next contiguous region in the device starting
707    * at the given byte offset.  Also return the underlying block device(s)
708    * if there is one.
709    *)
710   and get_next_extent disks (dev : device) offset =
711     let this_extent = dev#contiguous offset in
712
713     (* If this disk is a block_device (a member of the 'disks' list)
714      * then we've hit the bottom layer of devices, so just return it.
715      *)
716     if List.memq dev disks then
717       [dev, offset], this_extent
718     else (
719       let blocksize = dev#blocksize in
720       let block = offset /^ blocksize in
721       let offset_in_block = offset -^ block *^ blocksize in
722
723       (* Map from this block to the devices one layer down. *)
724       let devs = dev#map_block block in
725
726       (* Get the real device offsets, adding the offset from start of block. *)
727       let devs =
728         List.map
729           (fun (dev, dev_offset) -> dev, dev_offset +^ offset_in_block)
730           devs in
731
732       let devs =
733         List.map
734           (fun (dev, dev_offset) ->
735              get_next_extent disks dev dev_offset)
736           devs in
737
738       (* Work out the minimum contiguous extent from this offset. *)
739       let devs, extent =
740         let extents = List.map snd devs in
741         let devs = List.concat (List.map fst devs) in
742         let extent = List.fold_left min this_extent extents in
743         devs, extent in
744
745       devs, extent
746     )
747
748   and string_of_owner = function
749     | `Filesystem {fs_cb = {fs_cb_name = name}; fs_dev = fs_dev} ->
750         sprintf "%s(%s)" fs_dev#name name
751     | `PhysicalVolume { pv_uuid = pv_uuid } ->
752         "PV:" ^ pv_uuid
753     | `Partitions { parts_cb = {parts_cb_name = name} } ->
754         name
755   in
756
757   (* Build the list of segments. *)
758   let ownership : ownership_list = iter_over_machine machine in
759
760   (* Group the segments together by disk. *)
761   let ownership =
762     let ownership = List.sort ownership in
763     group_by ownership in
764
765   (* If debugging, print the segments that we found. *)
766   if !debug then (
767     List.iter (
768       fun (disk, segments) ->
769         eprintf "ownership segment list of %s %s:\n" machine.m_name disk#name;
770         List.iter (
771           fun (disk_offset, size, owner, owner_offset) ->
772             let blocksize = disk#blocksize in
773             let disk_offset_in_blocks, disk_offset_in_block =
774               disk_offset /^ blocksize, disk_offset %^ blocksize in
775             let size_in_blocks, size_in_block =
776               size /^ blocksize, size %^ blocksize in
777
778             eprintf "  %s[%s:%s] %s[%s:%s] %s@%s\n"
779               (Int63.to_string disk_offset)
780                 (Int63.to_string disk_offset_in_blocks)
781                 (Int63.to_string disk_offset_in_block)
782               (Int63.to_string size)
783                 (Int63.to_string size_in_blocks)
784                 (Int63.to_string size_in_block)
785               (string_of_owner owner)
786               (Int63.to_string owner_offset)
787         ) segments
788     ) ownership
789   );
790
791   (* Build the segment tree from the ownership list (of segments).
792    * For an explanation of this process see:
793    * http://en.wikipedia.org/wiki/Segment_tree
794    *)
795   let ownership =
796     List.map (
797       fun (disk, segments) ->
798         (* Construct the list of distinct endpoints. *)
799         let eps =
800           List.map
801             (fun (start, size, _, _) -> [start; start +^ size])
802             segments in
803         let eps = sort_uniq (List.concat eps) in
804
805         (* Construct the elementary intervals. *)
806         let elints =
807           let elints, lastpoint =
808             List.fold_left (
809               fun (elints, prevpoint) point ->
810                 ((point, point) :: (prevpoint, point) :: elints), point
811             ) ([], Int63.min_int) eps in
812           let elints = (lastpoint, Int63.max_int) :: elints in
813           List.rev elints in
814
815         if !debug then (
816           eprintf "elementary intervals for %s (%d in total):\n"
817             disk#name (List.length elints);
818           List.iter (
819             fun (startpoint, endpoint) ->
820               eprintf "  %s %s\n"
821                 (Int63.to_string startpoint) (Int63.to_string endpoint)
822           ) elints
823         );
824
825         (* Construct the binary tree of elementary intervals. *)
826         let tree =
827           (* Each elementary interval becomes a leaf. *)
828           let elints = List.map (fun elint -> Leaf elint) elints in
829           (* Recursively build this into a binary tree. *)
830           let rec make_layer = function
831             | [] -> []
832             | ([_] as x) -> x
833             (* Turn pairs of leaves at the bottom level into nodes. *)
834             | (Leaf _ as a) :: (Leaf _ as b) :: xs ->
835                 let xs = make_layer xs in
836                 Node (a, (), b) :: xs
837             (* Turn pairs of nodes at higher levels into nodes. *)
838             | (Node _ as left) :: ((Node _|Leaf _) as right) :: xs ->
839                 let xs = make_layer xs in
840                 Node (left, (), right) :: xs
841             | Leaf _ :: _ -> assert false (* never happens??? (I think) *)
842           in
843           let rec loop = function
844             | [] -> assert false
845             | [x] -> x
846             | xs -> loop (make_layer xs)
847           in
848           loop elints in
849
850         if !debug then (
851           let leaf_printer (startpoint, endpoint) =
852             sprintf "%s-%s"
853               (Int63.to_string startpoint) (Int63.to_string endpoint)
854           in
855           let node_printer () = "" in
856           print_binary_tree leaf_printer node_printer tree
857         );
858
859         (* Insert the segments into the tree one by one. *)
860         let tree =
861           (* For each node/leaf in the tree, add its interval and an
862            * empty list which will be used to store the segments.
863            *)
864           let rec interval_tree = function
865             | Leaf elint -> Leaf (elint, [])
866             | Node (left, (), right) ->
867                 let left = interval_tree left in
868                 let right = interval_tree right in
869                 let (leftstart, _) = interval_of_node left in
870                 let (_, rightend) = interval_of_node right in
871                 let interval = leftstart, rightend in
872                 Node (left, (interval, []), right)
873           and interval_of_node = function
874             | Leaf (elint, _) -> elint
875             | Node (_, (interval, _), _) -> interval
876           in
877
878           let tree = interval_tree tree in
879           (* This should always be true: *)
880           assert (interval_of_node tree = (Int63.min_int, Int63.max_int));
881
882           (* "Contained in" operator.
883            * 'a <-< b' iff 'a' is a subinterval of 'b'.
884            *      |<---- a ---->|
885            * |<----------- b ----------->|
886            *)
887           let (<-<) (a1, a2) (b1, b2) = b1 <= a1 && a2 <= b2 in
888
889           (* "Intersects" operator.
890            * 'a /\ b' iff intervals 'a' and 'b' overlap, eg:
891            *      |<---- a ---->|
892            *                |<----------- b ----------->|
893            *)
894           let ( /\ ) (a1, a2) (b1, b2) = a2 > b1 || b2 > a1 in
895
896           let rec insert_segment tree segment =
897             let start, size, owner, owner_offset = segment in
898             let seginterval = start, start +^ size in
899             let seg = owner, owner_offset in
900
901             match tree with
902             (* Test if we should insert into this leaf or node: *)
903             | Leaf (interval, segs) when interval <-< seginterval ->
904                 Leaf (interval, seg :: segs)
905             | Node (left, (interval, segs), right)
906                 when interval <-< seginterval ->
907                 Node (left, (interval, seg :: segs), right)
908
909             | (Leaf _) as leaf -> leaf
910
911             (* Else, should we insert into left or right subtrees? *)
912             | Node (left, i, right) ->
913                 let left =
914                   if seginterval /\ interval_of_node left then
915                     insert_segment left segment
916                   else
917                     left in
918                 let right =
919                   if seginterval /\ interval_of_node right then
920                     insert_segment right segment
921                   else
922                     right in
923                 Node (left, i, right)
924           in
925           let tree = List.fold_left insert_segment tree segments in
926           tree in
927
928         if !debug then (
929           let printer ((sp, ep), segments) =
930             sprintf "[%s-%s] " (Int63.to_string sp) (Int63.to_string ep) ^
931               String.concat ";"
932               (List.map (fun (owner,_) -> string_of_owner owner)
933                  segments)
934           in
935           print_binary_tree printer printer tree
936         );
937         (disk, tree)
938     ) ownership in
939
940   (* Return the ownership structure. *)
941   ownership
942
943 let get_owners_lookup machine ownership (disk : block_device) =
944   (* Get the correct tree. *)
945   let tree = List.assoc (disk :> device) ownership in
946
947   fun offset ->
948     (* Warning: This 'hot' code was carefully optimized based on
949      * feedback from 'gprof'.  Avoid fiddling with it.
950      *)
951     let rec query = function
952       | Leaf (_, segments) -> segments
953
954       (* Try to avoid expensive '@' operator if node segments is empty: *)
955       | Node ((Leaf ((_, leftend), _) | Node (_, ((_, leftend), _), _) as left),
956               (_, []),
957               right) ->
958           let subsegments =
959             if offset < leftend then query left else query right in
960           subsegments
961
962       (* ... or a singleton: *)
963       | Node ((Leaf ((_, leftend), _) | Node (_, ((_, leftend), _), _) as left),
964               (_, [segment]),
965               right) ->
966           let subsegments =
967             if offset < leftend then query left else query right in
968           segment :: subsegments
969
970       (* Normal recursive case: *)
971       | Node ((Leaf ((_, leftend), _) | Node (_, ((_, leftend), _), _) as left),
972               (_, segments),
973               right) ->
974           let subsegments =
975             if offset < leftend then query left else query right in
976           segments @ subsegments
977     in
978     let owners = query tree in
979
980     List.map (
981       fun (owner, owner_offset) -> (owner, offset -^ owner_offset)
982     ) owners
983
984 (* Find out if a disk offset is free.
985  * Current algorithm just checks that at least one owner says
986  * it is free.  We could be smarter about this.
987  *)
988 let offset_is_free owners =
989   List.exists (
990     function
991     | `Filesystem fs, offset ->
992         fs.fs_cb.fs_cb_offset_is_free fs offset
993     | `Partitions parts, offset ->
994         parts.parts_cb.parts_cb_offset_is_free parts offset
995     | `PhysicalVolume pv, offset ->
996         pv.pv_cb.lvm_cb_offset_is_free pv offset
997   ) owners