1 (* Diskimage library for reading disk images.
2 (C) Copyright 2007-2008 Richard W.M. Jones, Red Hat Inc.
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.
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.
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.
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.
31 let disk_block_size = ~^512
33 class virtual device =
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
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";
46 let blocksize = self#blocksize in
48 (* Break the request into blocks.
49 * Find the first and last blocks of this request.
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
55 (* Buffer for the result. *)
56 let buf = Buffer.create (Int63.to_int len) in
58 let not_mapped_error () = invalid_arg "device: read: block not mapped" in
60 (* Copy the first block (partial). *)
61 (match self#map_block first_blk with
62 | [] -> not_mapped_error ()
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
70 (* Copy the middle blocks. *)
72 if blk < last_blk then (
73 (match self#map_block blk with
74 | [] -> not_mapped_error ()
76 let str = dev#read ~^0 self#blocksize in
77 Buffer.add_string buf str
82 loop (Int63.succ first_blk);
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 ()
89 let len = (offset +^ len) -^ last_blk *^ blocksize in
90 let str = dev#read ~^0 len in
91 Buffer.add_string buf str
94 assert (Int63.to_int len = Buffer.length buf);
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)
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
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);
117 method name = filename
118 method blocksize = blocksize
119 method map_block _ = []
120 method contiguous offset =
122 method close () = close fd
125 (* A linear offset/size from an underlying device. *)
126 class offset_device name start size blocksize (dev : device) =
131 method read offset len =
132 if offset < ~^0 || len < ~^0 || offset +^ len > size then
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)
138 dev#read (start+^offset) len
139 method blocksize = blocksize
140 method map_block i = [dev, i *^ blocksize +^ start]
141 method contiguous offset =
145 (* A device with just a modified block size. *)
146 class blocksize_overlay new_blocksize (dev : 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
159 (* The null device. Any attempt to read generates an error. *)
160 let null_device : device =
163 method read _ _ = assert false
166 method blocksize = ~^1
167 method map_block _ = assert false
168 method contiguous _ = ~^0
172 m_name : string; (* Machine name. *)
173 m_disks : disk list; (* Machine disks. *)
175 (lv * filesystem) list; (* Machine LV filesystems. *)
178 d_name : string; (* Device name (eg "hda") *)
180 (* About the device itself. *)
181 d_dev : block_device; (* Disk device. *)
182 d_content : disk_content; (* What's on it. *)
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. *)
194 parts_cb : partitioner_callbacks; (* Partitioning scheme. *)
195 parts_dev : device; (* Partitions (whole) device. *)
196 parts : partition list (* Partitions. *)
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. *)
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. *)
211 (* Filesystems (also swap devices). *)
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. *)
227 (* Physical volumes. *)
229 pv_cb : lvm_callbacks; (* The LVM plug-in. *)
230 pv_dev : device; (* Device covering whole PV. *)
231 pv_uuid : string; (* UUID. *)
234 (* Logical volumes. *)
236 lv_dev : device; (* Logical volume device. *)
239 (* Tables of callbacks. *)
240 and partitioner_probe = device -> partitions
242 and partitioner_callbacks = {
244 parts_cb_name : string;
245 parts_cb_offset_is_free : partitions -> Int63.t -> bool;
248 and filesystem_probe = device -> filesystem
250 and filesystem_callbacks = {
253 fs_cb_printable_name : string;
254 fs_cb_offset_is_free : filesystem -> Int63.t -> bool;
257 and lvm_probe = device -> pv
259 and lvm_callbacks = {
261 lvm_cb_name : string;
262 lvm_cb_list_lvs : pv list -> lv list;
263 lvm_cb_offset_is_free : pv -> Int63.t -> bool;
266 let name_of_filesystem { fs_cb = { fs_cb_printable_name = name } } = name
268 (*----------------------------------------------------------------------*)
269 (* Helper functions. *)
271 (* Convert a UUID (containing '-' chars) to canonical form. *)
272 let canonical_uuid uuid =
273 let uuid' = String.make 32 ' ' in
275 for i = 0 to String.length uuid - 1 do
276 if !j >= 32 then invalid_arg "canonical_uuid";
278 if c <> '-' then ( uuid'.[!j] <- c; incr j )
280 if !j <> 32 then invalid_arg "canonical_uuid";
283 (* This version by Isaac Trotts. *)
284 let group_by ?(cmp = Pervasives.compare) ls =
287 (fun acc (day1, x1) ->
290 | (day2, ls2) :: acctl ->
292 then (day1, x1 :: ls2) :: acctl
293 else (day1, [x1]) :: acc)
297 let ls' = List.rev ls' in
298 List.map (fun (x, xs) -> x, List.rev xs) ls'
300 let rec uniq ?(cmp = Pervasives.compare) = function
303 | x :: y :: xs when cmp x y = 0 ->
308 let sort_uniq ?cmp xs =
309 let xs = ExtList.List.sort ?cmp xs in
310 let xs = uniq ?cmp xs in
314 if a < b then a :: range (a+1) b
317 (*----------------------------------------------------------------------*)
320 let partitioners = ref []
321 let filesystems = ref []
324 let register_plugin ?partitioner ?filesystem ?lvm id =
325 (match partitioner with
327 | Some probe -> partitioners := !partitioners @ [id, probe]
329 (match filesystem with
331 | Some probe -> filesystems := !filesystems @ [id, probe]
335 | Some probe -> lvms := !lvms @ [id, probe]
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
343 | (_, probe) :: rest ->
345 with Not_found -> loop rest
347 let r = loop !partitioners in
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
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
362 | (_, probe) :: rest ->
364 with Not_found -> loop rest
366 let r = loop !filesystems in
369 | None -> eprintf "no filesystem found on %s\n%!" dev#name
371 eprintf "found a filesystem on %s:\n" dev#name;
372 eprintf "\t%s\n%!" fs.fs_cb.fs_cb_name
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
381 | (_, probe) :: rest ->
383 with Not_found -> loop rest
385 let r = loop !lvms in
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
394 (* This allows plug-ins to attach their own private data to
395 * the normal plug-in structures (partitions, filesystem, pv, etc.)
397 let private_data_functions get_key =
398 let h = Hashtbl.create 13 in
400 Hashtbl.replace h (get_key struc) data),
402 try Hashtbl.find h (get_key struc)
403 with Not_found -> assert false (* internal error in the plug-in *))
405 (*----------------------------------------------------------------------*)
406 (* Create machine description. *)
407 let open_machine name disks =
408 let disks = List.map (
410 let dev = new block_device path disk_block_size (* XXX *) in
411 { d_name = name; d_dev = dev; d_content = `Unknown }
413 { m_name = name; m_disks = disks; m_lv_filesystems = [] }
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
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
428 { disk with d_content = `Partitions parts }
430 (* Not partitioned. Does it contain a filesystem? *)
431 let fs = probe_for_filesystem dev in
434 { disk with d_content = `Filesystem fs }
436 (* Not partitioned, no filesystem, is it a PV? *)
437 let pv = probe_for_pv dev in
440 { disk with d_content = `PhysicalVolume pv }
442 disk (* Spare/unknown. *)
445 (* Now we have either detected partitions or a filesystem on each
446 * physical device (or perhaps neither). See what is on those
449 let m_disks = List.map (
451 | ({ d_dev = dev; d_content = `Partitions parts } as disk) ->
454 if p.part_status = Bootable || p.part_status = Nonbootable then (
455 let fs = probe_for_filesystem p.part_dev in
458 { p with part_content = `Filesystem fs }
461 let pv = probe_for_pv p.part_dev in
464 { p with part_content = `PhysicalVolume lvm_name }
466 p (* Spare/unknown. *)
469 let parts = { parts with parts = ps } in
470 { disk with d_content = `Partitions parts }
474 (* LVM filesystem detection
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.
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
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.
487 (* First: LV detection.
488 * Find all physical volumes, can be disks or partitions.
490 let pvs_on_disks = List.filter_map (
492 | { d_content = `PhysicalVolume pv } -> Some pv
495 let pvs_on_partitions = List.map (
497 | { d_content = `Partitions { parts = parts } } ->
500 | { part_content = `PhysicalVolume pv } -> Some pv
505 let lvs = List.concat (pvs_on_disks :: pvs_on_partitions) in
507 (* Second: filesystem on LV detection.
508 * Group the LVs by LVM plug-in ID.
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
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
520 (* lvs is a list of potential LV devices. Now run them through the
521 * probes to see if any contain filesystems.
525 fun ({ lv_dev = dev } as lv) ->
526 match probe_for_filesystem dev with
527 | Some fs -> Some (lv, fs)
533 m_lv_filesystems = filesystems }
535 (*----------------------------------------------------------------------*)
537 (* We describe the ownership of each part of the disk using a
538 * segment tree. http://en.wikipedia.org/wiki/Segment_tree
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'.
547 (* General binary tree type. Data 'a is stored in the leaves and 'b
548 * is stored in the nodes.
550 type ('a,'b) binary_tree =
552 | Node of ('a,'b) binary_tree * 'b * ('a,'b) binary_tree
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. *)
559 let hash = Hashtbl.create 13 in
561 try Hashtbl.find hash node
563 let i = incr i; !i in
564 let label = "n" ^ string_of_int i in
565 Hashtbl.add hash node label;
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);
581 eprintf "/* Use 'dot -Tpng foo.dot > foo.png' to convert to a png file. */\n";
582 eprintf "digraph G {\n";
587 [ `Filesystem of filesystem
588 | `Partitions of partitions
589 | `PhysicalVolume of pv ]
591 (* A segment describes the owner of a range of disk addresses. *)
592 type segment = owner * int63 (* owner, owner offset *)
594 type interval = int63 * int63 (* start point, end point (bytes) *)
596 (* The special segment tree structure that we construct in create_ownership. *)
598 (interval * segment list, interval * segment list) binary_tree
601 (device * (* block_device (disk) *)
602 segment_tree) list (* segment tree for this disk *)
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 *)
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).
617 let rec iter_over_machine
618 ({m_disks = disks; m_lv_filesystems = lv_filesystems} as machine) =
620 (* No segments to begin with. *)
621 let ownership = [] in
623 (* Iterate over disks. *)
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
637 (* Iterate over LV filesystems. *)
640 fun ownership (lv, fs) ->
641 let owner = `Filesystem fs in
642 iter_over_filesystem machine ownership fs owner
643 ) ownership lv_filesystems in
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
651 (* Iterate over the blocks in a set of partitions, then
652 * iterate over the contents of the partitions.
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
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
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
675 (* Iterate over the blocks in a device, assigning ownership to 'owner'
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.
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
688 let rec loop ownership offset =
689 if offset < size then (
690 let devs, extent = get_next_extent disks dev offset in
692 eprintf "warning: no device found under %s\n"
693 (string_of_owner owner);
696 fun ownership (disk, disk_offset) ->
697 let elem = disk, (disk_offset, extent, owner, offset) in
700 loop ownership (offset +^ extent)
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)
710 and get_next_extent disks (dev : device) offset =
711 let this_extent = dev#contiguous offset in
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.
716 if List.memq dev disks then
717 [dev, offset], this_extent
719 let blocksize = dev#blocksize in
720 let block = offset /^ blocksize in
721 let offset_in_block = offset -^ block *^ blocksize in
723 (* Map from this block to the devices one layer down. *)
724 let devs = dev#map_block block in
726 (* Get the real device offsets, adding the offset from start of block. *)
729 (fun (dev, dev_offset) -> dev, dev_offset +^ offset_in_block)
734 (fun (dev, dev_offset) ->
735 get_next_extent disks dev dev_offset)
738 (* Work out the minimum contiguous extent from this offset. *)
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
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 } ->
753 | `Partitions { parts_cb = {parts_cb_name = name} } ->
757 (* Build the list of segments. *)
758 let ownership : ownership_list = iter_over_machine machine in
760 (* Group the segments together by disk. *)
762 let ownership = List.sort ownership in
763 group_by ownership in
765 (* If debugging, print the segments that we found. *)
768 fun (disk, segments) ->
769 eprintf "ownership segment list of %s %s:\n" machine.m_name disk#name;
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
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)
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
797 fun (disk, segments) ->
798 (* Construct the list of distinct endpoints. *)
801 (fun (start, size, _, _) -> [start; start +^ size])
803 let eps = sort_uniq (List.concat eps) in
805 (* Construct the elementary intervals. *)
807 let elints, lastpoint =
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
816 eprintf "elementary intervals for %s (%d in total):\n"
817 disk#name (List.length elints);
819 fun (startpoint, endpoint) ->
821 (Int63.to_string startpoint) (Int63.to_string endpoint)
825 (* Construct the binary tree of elementary intervals. *)
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
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) *)
843 let rec loop = function
846 | xs -> loop (make_layer xs)
851 let leaf_printer (startpoint, endpoint) =
853 (Int63.to_string startpoint) (Int63.to_string endpoint)
855 let node_printer () = "" in
856 print_binary_tree leaf_printer node_printer tree
859 (* Insert the segments into the tree one by one. *)
861 (* For each node/leaf in the tree, add its interval and an
862 * empty list which will be used to store the segments.
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
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));
882 (* "Contained in" operator.
883 * 'a <-< b' iff 'a' is a subinterval of 'b'.
885 * |<----------- b ----------->|
887 let (<-<) (a1, a2) (b1, b2) = b1 <= a1 && a2 <= b2 in
889 (* "Intersects" operator.
890 * 'a /\ b' iff intervals 'a' and 'b' overlap, eg:
892 * |<----------- b ----------->|
894 let ( /\ ) (a1, a2) (b1, b2) = a2 > b1 || b2 > a1 in
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
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)
909 | (Leaf _) as leaf -> leaf
911 (* Else, should we insert into left or right subtrees? *)
912 | Node (left, i, right) ->
914 if seginterval /\ interval_of_node left then
915 insert_segment left segment
919 if seginterval /\ interval_of_node right then
920 insert_segment right segment
923 Node (left, i, right)
925 let tree = List.fold_left insert_segment tree segments in
929 let printer ((sp, ep), segments) =
930 sprintf "[%s-%s] " (Int63.to_string sp) (Int63.to_string ep) ^
932 (List.map (fun (owner,_) -> string_of_owner owner)
935 print_binary_tree printer printer tree
940 (* Return the ownership structure. *)
943 let get_owners_lookup machine ownership (disk : block_device) =
944 (* Get the correct tree. *)
945 let tree = List.assoc (disk :> device) ownership in
948 (* Warning: This 'hot' code was carefully optimized based on
949 * feedback from 'gprof'. Avoid fiddling with it.
951 let rec query = function
952 | Leaf (_, segments) -> segments
954 (* Try to avoid expensive '@' operator if node segments is empty: *)
955 | Node ((Leaf ((_, leftend), _) | Node (_, ((_, leftend), _), _) as left),
959 if offset < leftend then query left else query right in
962 (* ... or a singleton: *)
963 | Node ((Leaf ((_, leftend), _) | Node (_, ((_, leftend), _), _) as left),
967 if offset < leftend then query left else query right in
968 segment :: subsegments
970 (* Normal recursive case: *)
971 | Node ((Leaf ((_, leftend), _) | Node (_, ((_, leftend), _), _) as left),
975 if offset < leftend then query left else query right in
976 segments @ subsegments
978 let owners = query tree in
981 fun (owner, owner_offset) -> (owner, offset -^ owner_offset)
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.
988 let offset_is_free owners =
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