389358b98c3bb5f17f55abdd601afbcd32da5c33
[virt-df.git] / lib / diskimage.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 Printf
21 open ExtList
22 open Unix
23
24 open Int63.Operators
25
26 include Diskimage_utils
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 let partition_types = [
34   Diskimage_mbr.plugin_id,
35     ("MBR", Diskimage_mbr.probe);
36 ]
37
38 let filesystem_types = [
39   Diskimage_ext2.plugin_id,
40     ("Linux ext2/3", Diskimage_ext2.probe);
41   Diskimage_linux_swap.plugin_id,
42     ("Linux swap", Diskimage_linux_swap.probe);
43   Diskimage_linux_swsuspend.plugin_id,
44     ("Linux s/w suspend", Diskimage_linux_swsuspend.probe);
45 ]
46
47 let lvm_types = [
48   Diskimage_lvm2.plugin_id,
49     ("Linux LVM2", Diskimage_lvm2.probe, Diskimage_lvm2.list);
50 ]
51
52 let name_of_parts id =
53   let name, _ = List.assoc id partition_types in
54   name
55 let name_of_filesystem id =
56   let name, _ = List.assoc id filesystem_types in
57   name
58 let name_of_lvm id =
59   let name, _, _ = List.assoc id lvm_types in
60   name
61
62 (* Probe a device for partitions.  Returns [Some parts] or [None]. *)
63 let probe_for_partitions dev =
64   if !debug then eprintf "probing for partitions on %s ...\n%!" dev#name;
65   let rec loop = function
66     | [] -> None
67     | (parts_plugin_id, (_, probe_fn)) :: rest ->
68         try Some (probe_fn dev)
69         with Not_found -> loop rest
70   in
71   let r = loop partition_types in
72   if !debug then (
73     match r with
74     | None -> eprintf "no partitions found on %s\n%!" dev#name
75     | Some { parts_plugin_id = name; parts = parts } ->
76         eprintf "found %d %s partitions on %s\n"
77           (List.length parts) name dev#name
78   );
79   r
80
81 (* Probe a device for a filesystem.  Returns [Some fs] or [None]. *)
82 let probe_for_filesystem dev =
83   if !debug then eprintf "probing for a filesystem on %s ...\n%!" dev#name;
84   let rec loop = function
85     | [] -> None
86     | (fs_name, (_, probe_fn)) :: rest ->
87         try Some (probe_fn dev)
88         with Not_found -> loop rest
89   in
90   let r = loop filesystem_types in
91   if !debug then (
92     match r with
93     | None -> eprintf "no filesystem found on %s\n%!" dev#name
94     | Some fs ->
95         eprintf "found a filesystem on %s:\n" dev#name;
96         eprintf "\t%s\n%!" fs.fs_plugin_id
97   );
98   r
99
100 (* Probe a device for a PV.  Returns [Some lvm_name] or [None]. *)
101 let probe_for_pv dev =
102   if !debug then eprintf "probing if %s is a PV ...\n%!" dev#name;
103   let rec loop = function
104     | [] -> None
105     | (lvm_name, (_, probe_fn, _)) :: rest ->
106         try Some (probe_fn lvm_name dev)
107         with Not_found -> loop rest
108   in
109   let r = loop lvm_types in
110   if !debug then (
111     match r with
112     | None -> eprintf "no PV found on %s\n%!" dev#name
113     | Some { lvm_plugin_id = name } ->
114         eprintf "%s contains a %s PV\n%!" dev#name name
115   );
116   r
117
118 let list_lvs lvm_name devs =
119   let _, _, list_lvs_fn = List.assoc lvm_name lvm_types in
120   list_lvs_fn devs
121
122 (* Create machine description. *)
123 let open_machine name disks =
124   let disks = List.map (
125     fun (name, path) ->
126       let dev = new block_device path disk_block_size (* XXX *) in
127       { d_name = name; d_dev = dev; d_content = `Unknown }
128   ) disks in
129   { m_name = name; m_disks = disks; m_lv_filesystems = [] }
130
131 let close_machine { m_disks = m_disks } =
132   (* Only close the disks, assume all other devices are derived from them. *)
133   List.iter (fun { d_dev = d_dev } -> d_dev#close ()) m_disks
134
135 (* Main scanning function for filesystems. *)
136 let scan_machine ({ m_disks = m_disks } as machine) =
137   let m_disks = List.map (
138     fun ({ d_dev = dev } as disk) ->
139       let dev = (dev :> device) in
140       (* See if it is partitioned first. *)
141       let parts = probe_for_partitions dev in
142       match parts with
143       | Some parts ->
144           { disk with d_content = `Partitions parts }
145       | None ->
146           (* Not partitioned.  Does it contain a filesystem? *)
147           let fs = probe_for_filesystem dev in
148           match fs with
149           | Some fs ->
150               { disk with d_content = `Filesystem fs }
151           | None ->
152               (* Not partitioned, no filesystem, is it a PV? *)
153               let pv = probe_for_pv dev in
154               match pv with
155               | Some lvm_name ->
156                   { disk with d_content = `PhysicalVolume lvm_name }
157               | None ->
158                   disk (* Spare/unknown. *)
159   ) m_disks in
160
161   (* Now we have either detected partitions or a filesystem on each
162    * physical device (or perhaps neither).  See what is on those
163    * partitions.
164    *)
165   let m_disks = List.map (
166     function
167     | ({ d_dev = dev; d_content = `Partitions parts } as disk) ->
168         let ps = List.map (
169           fun p ->
170             if p.part_status = Bootable || p.part_status = Nonbootable then (
171               let fs = probe_for_filesystem p.part_dev in
172               match fs with
173               | Some fs ->
174                   { p with part_content = `Filesystem fs }
175               | None ->
176                   (* Is it a PV? *)
177                   let pv = probe_for_pv p.part_dev in
178                   match pv with
179                   | Some lvm_name ->
180                       { p with part_content = `PhysicalVolume lvm_name }
181                   | None ->
182                       p (* Spare/unknown. *)
183             ) else p
184         ) parts.parts in
185         let parts = { parts with parts = ps } in
186         { disk with d_content = `Partitions parts }
187     | disk -> disk
188   ) m_disks in
189
190   (* LVM filesystem detection
191    *
192    * Look for all disks/partitions which have been identified as PVs
193    * and pass those back to the respective LVM plugin for LV detection.
194    *
195    * (Note - a two-stage process because an LV can be spread over
196    * several PVs, so we have to detect all PVs belonging to a
197    * domain first).
198    *
199    * XXX To deal with RAID (ie. md devices) we will need to loop
200    * around here because RAID is like LVM except that they normally
201    * present as block devices which can be used by LVM.
202    *)
203   (* First: LV detection.
204    * Find all physical volumes, can be disks or partitions.
205    *)
206   let pvs_on_disks = List.filter_map (
207     function
208     | { d_dev = d_dev;
209         d_content = `PhysicalVolume pv } -> Some (pv, (d_dev :> device))
210     | _ -> None
211   ) m_disks in
212   let pvs_on_partitions = List.map (
213     function
214     | { d_content = `Partitions { parts = parts } } ->
215         List.filter_map (
216           function
217           | { part_dev = part_dev;
218               part_content = `PhysicalVolume pv } ->
219               Some (pv, part_dev)
220           | _ -> None
221         ) parts
222     | _ -> []
223   ) m_disks in
224   let lvs = List.concat (pvs_on_disks :: pvs_on_partitions) in
225
226   (* Second: filesystem on LV detection.
227    * Group the LVs by plug-in type.
228    *)
229   let cmp (a,_) (b,_) = compare a b in
230   let lvs = List.sort ~cmp lvs in
231   let lvs = group_by lvs in
232
233   let lvs =
234     List.map (fun (pv, devs) -> list_lvs pv.lvm_plugin_id devs) lvs in
235   let lvs = List.concat lvs in
236
237   (* lvs is a list of potential LV devices.  Now run them through the
238    * probes to see if any contain filesystems.
239    *)
240   let filesystems =
241     List.filter_map (
242       fun ({ lv_dev = dev } as lv) ->
243         match probe_for_filesystem dev with
244         | Some fs -> Some (lv, fs)
245         | None -> None
246     ) lvs in
247
248   { machine with
249       m_disks = m_disks;
250       m_lv_filesystems = filesystems }
251
252 (* Ownership tables. *)
253 let create_ownership machine =
254   (* Iterate over all the things which can claim ownership of a
255    * disk block (filesystems, partitions, PVs).
256    *
257    * A single disk block can be "owned" by several things (eg. it
258    * could contain an LV filesystem, on a PV, on a partition).
259    *)
260   let rec iter_over_machine
261       {m_disks = disks; m_lv_filesystems = lv_filesystems} =
262     List.iter (
263       function
264       | { d_content = (`Filesystem fs as owner) } ->
265           iter_over_filesystem disks fs owner
266       | { d_content = (`Partitions parts as owner) } ->
267           iter_over_partitions disks parts owner
268       | { d_content = (`PhysicalVolume pv as owner) } ->
269           iter_over_pv disks pv owner
270       | { d_content = `Unknown } -> ()
271     ) disks;
272     List.iter (
273       fun (lv, fs) ->
274         let owner = `Filesystem fs in
275         iter_over_filesystem disks fs owner
276     ) lv_filesystems
277
278   (* Iterate over the blocks in a single filesystem. *)
279   and iter_over_filesystem disks {fs_dev = dev} owner =
280     iter_over_device disks dev owner
281
282   (* Iterate over the blocks in a set of partitions, then
283    * iterate over the contents of the partitions.
284    *)
285   and iter_over_partitions disks {parts = parts; parts_dev = parts_dev} owner =
286     iter_over_device disks parts_dev owner;
287
288     List.iter (
289       function
290       | { part_content = (`Filesystem fs as owner) } ->
291           iter_over_filesystem disks fs owner
292       | { part_content = (`PhysicalVolume pv as owner) } ->
293           iter_over_pv disks pv owner
294       | { part_content = `Unknown } -> ()
295     ) parts
296
297   (* Iterate over the blocks in a PV. *)
298   and iter_over_pv disks {pv_dev = dev} owner =
299     iter_over_device disks dev owner
300
301   (* Iterate over the blocks in a device, assigning ownership to 'owner'
302    *
303    * In reality (1): There can be several owners for each block, so we
304    * incrementally add ownership.  The add_ownership function takes
305    * care of handling overlapping ranges, using an AVL tree.
306    * In reality (2): Iterating over blocks would take ages and result
307    * in a very inefficient ownership representation.  Instead we look
308    * at minimum contiguous extents.
309    *)
310   and iter_over_device disks dev owner =
311     let size = dev#size in
312
313     let rec loop offset =
314       if offset < size then (
315         let extent =
316           let devs, extent = get_next_extent disks dev offset in
317           if devs = [] then
318             eprintf "warning: no device found under %s\n"
319               (string_of_owner owner);
320           List.iter (
321             fun (dev, dev_offset) ->
322               add_ownership dev dev_offset extent owner
323           ) devs;
324           extent in
325         loop (offset +^ extent)
326       )
327     in
328     loop ~^0
329
330   (* Return the length of the next contiguous region in the device starting
331    * at the given byte offset.  Also return the underlying block device(s)
332    * if there is one.
333    *)
334   and get_next_extent disks (dev : device) offset =
335     let disks = List.map (fun { d_dev = dev } -> (dev :> device)) disks in
336     map_recursively disks dev offset
337
338   and map_recursively disks dev offset =
339     let this_extent = dev#contiguous offset in
340
341     (* If this disk is a block_device (a member of the 'disks' list)
342      * then we've hit the bottom layer of devices, so just return it.
343      *)
344     if List.memq dev disks then
345       [dev, offset], this_extent
346     else (
347       let blocksize = dev#blocksize in
348       let block = offset /^ blocksize in
349       let offset_in_block = offset -^ block *^ blocksize in
350
351       (* Map from this block to the devices one layer down. *)
352       let devs = dev#map_block block in
353
354       (* Get the real device offsets, adding the offset from start of block. *)
355       let devs =
356         List.map
357           (fun (dev, dev_offset) -> dev, dev_offset +^ offset_in_block)
358           devs in
359
360       let devs =
361         List.map
362           (fun (dev, dev_offset) ->
363              map_recursively disks dev dev_offset)
364           devs in
365
366       (* Work out the minimum contiguous extent from this offset. *)
367       let devs, extent =
368         let extents = List.map snd devs in
369         let devs = List.concat (List.map fst devs) in
370         let extent = List.fold_left min this_extent extents in
371         devs, extent in
372
373       devs, extent
374     )
375
376   and string_of_owner = function
377     | `Filesystem {fs_plugin_id = fs_plugin_id; fs_dev = fs_dev} ->
378         sprintf "%s(%s)" fs_dev#name fs_plugin_id
379     | `PhysicalVolume { pv_uuid = pv_uuid } ->
380         "PV:" ^ pv_uuid
381     | `Partitions { parts_plugin_id = parts_plugin_id } ->
382         parts_plugin_id
383
384   and add_ownership dev offset extent owner =
385     let blocksize = dev#blocksize in
386     let offset_in_blocks, offset_in_block =
387       offset /^ blocksize, offset %^ blocksize in
388     let extent_in_blocks, extent_in_block =
389       extent /^ blocksize, extent %^ blocksize in
390
391     eprintf "add_ownership: %s %s[%s:%s] %s[%s:%s] %s\n"
392       dev#name
393       (Int63.to_string offset)
394         (Int63.to_string offset_in_blocks)
395         (Int63.to_string offset_in_block)
396       (Int63.to_string extent)
397         (Int63.to_string extent_in_blocks)
398         (Int63.to_string extent_in_block)
399       (string_of_owner owner)
400   in
401   iter_over_machine machine
402
403