resize: Refactor the code for creating target partitions.
[libguestfs.git] / resize / resize.ml
1 (* virt-resize
2  * Copyright (C) 2010-2011 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 Printf
20
21 module G = Guestfs
22
23 open Utils
24
25 (* Minimum surplus before we create an extra partition. *)
26 let min_extra_partition = 10L *^ 1024L *^ 1024L
27
28 (* Command line argument parsing. *)
29 let prog = Filename.basename Sys.executable_name
30
31 let infile, outfile, copy_boot_loader, debug, deletes, dryrun,
32   expand, expand_content, extra_partition, format, ignores,
33   lv_expands, machine_readable, ntfsresize_force, output_format,
34   quiet, resizes, resizes_force, shrink =
35   let display_version () =
36     let g = new G.guestfs () in
37     let version = g#version () in
38     printf "virt-resize %Ld.%Ld.%Ld%s\n"
39       version.G.major version.G.minor version.G.release version.G.extra;
40     exit 0
41   in
42
43   let add xs s = xs := s :: !xs in
44
45   let copy_boot_loader = ref true in
46   let debug = ref false in
47   let deletes = ref [] in
48   let dryrun = ref false in
49   let expand = ref "" in
50   let set_expand s =
51     if s = "" then error "%s: empty --expand option" prog
52     else if !expand <> "" then error "--expand option given twice"
53     else expand := s
54   in
55   let expand_content = ref true in
56   let extra_partition = ref true in
57   let format = ref "" in
58   let ignores = ref [] in
59   let lv_expands = ref [] in
60   let machine_readable = ref false in
61   let ntfsresize_force = ref false in
62   let output_format = ref "" in
63   let quiet = ref false in
64   let resizes = ref [] in
65   let resizes_force = ref [] in
66   let shrink = ref "" in
67   let set_shrink s =
68     if s = "" then error "empty --shrink option"
69     else if !shrink <> "" then error "--shrink option given twice"
70     else shrink := s
71   in
72
73   let argspec = Arg.align [
74     "--no-copy-boot-loader", Arg.Clear copy_boot_loader, " Don't copy boot loader";
75     "-d",        Arg.Set debug,             " Enable debugging messages";
76     "--debug",   Arg.Set debug,             " -\"-";
77     "--delete",  Arg.String (add deletes),  "part Delete partition";
78     "--expand",  Arg.String set_expand,     "part Expand partition";
79     "--no-expand-content", Arg.Clear expand_content, " Don't expand content";
80     "--no-extra-partition", Arg.Clear extra_partition, " Don't create extra partition";
81     "--format",  Arg.Set_string format,     "format Format of input disk";
82     "--ignore",  Arg.String (add ignores),  "part Ignore partition";
83     "--lv-expand", Arg.String (add lv_expands), "lv Expand logical volume";
84     "--LV-expand", Arg.String (add lv_expands), "lv -\"-";
85     "--lvexpand", Arg.String (add lv_expands), "lv -\"-";
86     "--LVexpand", Arg.String (add lv_expands), "lv -\"-";
87     "--machine-readable", Arg.Set machine_readable, " Make output machine readable";
88     "-n",        Arg.Set dryrun,            " Don't perform changes";
89     "--dryrun",  Arg.Set dryrun,            " -\"-";
90     "--dry-run", Arg.Set dryrun,            " -\"-";
91     "--ntfsresize-force", Arg.Set ntfsresize_force, " Force ntfsresize";
92     "--output-format", Arg.Set_string format, "format Format of output disk";
93     "-q",        Arg.Set quiet,             " Don't print the summary";
94     "--quiet",   Arg.Set quiet,             " -\"-";
95     "--resize",  Arg.String (add resizes),  "part=size Resize partition";
96     "--resize-force", Arg.String (add resizes_force), "part=size Forcefully resize partition";
97     "--shrink",  Arg.String set_shrink,     "part Shrink partition";
98     "-V",        Arg.Unit display_version,  " Display version and exit";
99     "--version", Arg.Unit display_version,  " -\"-";
100   ] in
101   let disks = ref [] in
102   let anon_fun s = disks := s :: !disks in
103   let usage_msg =
104     sprintf "\
105 %s: resize a virtual machine disk
106
107 A short summary of the options is given below.  For detailed help please
108 read the man page virt-resize(1).
109 "
110       prog in
111   Arg.parse argspec anon_fun usage_msg;
112
113   let debug = !debug in
114   if debug then (
115     eprintf "command line:";
116     List.iter (eprintf " %s") (Array.to_list Sys.argv);
117     prerr_newline ()
118   );
119
120   (* Dereference the rest of the args. *)
121   let copy_boot_loader = !copy_boot_loader in
122   let deletes = List.rev !deletes in
123   let dryrun = !dryrun in
124   let expand = match !expand with "" -> None | str -> Some str in
125   let expand_content = !expand_content in
126   let extra_partition = !extra_partition in
127   let format = match !format with "" -> None | str -> Some str in
128   let ignores = List.rev !ignores in
129   let lv_expands = List.rev !lv_expands in
130   let machine_readable = !machine_readable in
131   let ntfsresize_force = !ntfsresize_force in
132   let output_format = match !output_format with "" -> None | str -> Some str in
133   let quiet = !quiet in
134   let resizes = List.rev !resizes in
135   let resizes_force = List.rev !resizes_force in
136   let shrink = match !shrink with "" -> None | str -> Some str in
137
138   (* No arguments and machine-readable mode?  Print out some facts
139    * about what this binary supports.  We only need to print out new
140    * things added since this option, or things which depend on features
141    * of the appliance.
142    *)
143   if !disks = [] && machine_readable then (
144     printf "virt-resize\n";
145     printf "ntfsresize-force\n";
146     printf "32bitok\n";
147     printf "128-sector-alignment\n";
148     let g = new G.guestfs () in
149     g#add_drive_opts "/dev/null";
150     g#launch ();
151     if feature_available g [| "ntfsprogs"; "ntfs3g" |] then
152       printf "ntfs\n";
153     if feature_available g [| "btrfs" |] then
154       printf "btrfs\n";
155     exit 0
156   );
157
158   (* Verify we got exactly 2 disks. *)
159   let infile, outfile =
160     match List.rev !disks with
161     | [infile; outfile] -> infile, outfile
162     | _ ->
163         error "usage is: %s [--options] indisk outdisk" prog in
164
165   infile, outfile, copy_boot_loader, debug, deletes, dryrun,
166   expand, expand_content, extra_partition, format, ignores,
167   lv_expands, machine_readable, ntfsresize_force, output_format,
168   quiet, resizes, resizes_force, shrink
169
170 (* Default to true, since NTFS and btrfs support are usually available. *)
171 let ntfs_available = ref true
172 let btrfs_available = ref true
173
174 (* Add in and out disks to the handle and launch. *)
175 let connect_both_disks () =
176   let g = new G.guestfs () in
177   if debug then g#set_trace true;
178   g#add_drive_opts ?format ~readonly:true infile;
179   g#add_drive_opts ?format:output_format ~readonly:false outfile;
180   if not quiet then Progress.set_up_progress_bar ~machine_readable g;
181   g#launch ();
182
183   (* Set the filter to /dev/sda, in case there are any rogue
184    * PVs lying around on the target disk.
185    *)
186   g#lvm_set_filter [|"/dev/sda"|];
187
188   (* Update features available in the daemon. *)
189   ntfs_available := feature_available g [|"ntfsprogs"; "ntfs3g"|];
190   btrfs_available := feature_available g [|"btrfs"|];
191
192   g
193
194 let g =
195   if not quiet then
196     printf "Examining %s ...\n%!" infile;
197
198   let g = connect_both_disks () in
199
200   g
201
202 (* Get the size in bytes of each disk.
203  *
204  * Originally we computed this by looking at the same of the host file,
205  * but of course this failed for qcow2 images (RHBZ#633096).  The right
206  * way to do it is with g#blockdev_getsize64.
207  *)
208 let sectsize, insize, outsize =
209   let sectsize = g#blockdev_getss "/dev/sdb" in
210   let insize = g#blockdev_getsize64 "/dev/sda" in
211   let outsize = g#blockdev_getsize64 "/dev/sdb" in
212   if debug then (
213     eprintf "%s size %Ld bytes\n" infile insize;
214     eprintf "%s size %Ld bytes\n" outfile outsize
215   );
216   sectsize, insize, outsize
217
218 let max_bootloader =
219   (* In reality the number of sectors containing boot loader data will be
220    * less than this (although Windows 7 defaults to putting the first
221    * partition on sector 2048, and has quite a large boot loader).
222    *
223    * However make this large enough to be sure that we have copied over
224    * the boot loader.  We could also do this by looking for the sector
225    * offset of the first partition.
226    *
227    * It doesn't matter if we copy too much.
228    *)
229   4096 * 512
230
231 (* Check the disks are at least as big as the bootloader. *)
232 let () =
233   if insize < Int64.of_int max_bootloader then
234     error "%s: file is too small to be a disk image (%Ld bytes)"
235       infile insize;
236   if outsize < Int64.of_int max_bootloader then
237     error "%s: file is too small to be a disk image (%Ld bytes)"
238       outfile outsize
239
240 (* Build a data structure describing the source disk's partition layout. *)
241 type partition = {
242   p_name : string;               (* Device name, like /dev/sda1. *)
243   p_part : G.partition;          (* SOURCE partition data from libguestfs. *)
244   p_bootable : bool;             (* Is it bootable? *)
245   p_mbr_id : int option;         (* MBR ID, if it has one. *)
246   p_type : partition_content;    (* Content type and content size. *)
247
248   (* What we're going to do: *)
249   mutable p_operation : partition_operation;
250   p_target_partnum : int;        (* TARGET partition number. *)
251   p_target_start : int64;        (* TARGET partition start (sector num). *)
252   p_target_end : int64;          (* TARGET partition end (sector num). *)
253 }
254 and partition_content =
255   | ContentUnknown               (* undetermined *)
256   | ContentPV of int64           (* physical volume (size of PV) *)
257   | ContentFS of string * int64  (* mountable filesystem (FS type, FS size) *)
258 and partition_operation =
259   | OpCopy                       (* copy it as-is, no resizing *)
260   | OpIgnore                     (* ignore it (create on target, but don't
261                                     copy any content) *)
262   | OpDelete                     (* delete it *)
263   | OpResize of int64            (* resize it to the new size *)
264
265 let rec debug_partition p =
266   eprintf "%s:\n" p.p_name;
267   eprintf "\tpartition data: %ld %Ld-%Ld (%Ld bytes)\n"
268     p.p_part.G.part_num p.p_part.G.part_start p.p_part.G.part_end
269     p.p_part.G.part_size;
270   eprintf "\tbootable: %b\n" p.p_bootable;
271   eprintf "\tpartition ID: %s\n"
272     (match p.p_mbr_id with None -> "(none)" | Some i -> sprintf "0x%x" i);
273   eprintf "\tcontent: %s\n" (string_of_partition_content p.p_type)
274 and string_of_partition_content = function
275   | ContentUnknown -> "unknown data"
276   | ContentPV sz -> sprintf "LVM PV (%Ld bytes)" sz
277   | ContentFS (fs, sz) -> sprintf "filesystem %s (%Ld bytes)" fs sz
278 and string_of_partition_content_no_size = function
279   | ContentUnknown -> "unknown data"
280   | ContentPV _ -> sprintf "LVM PV"
281   | ContentFS (fs, _) -> sprintf "filesystem %s" fs
282
283 let get_partition_content =
284   let pvs_full = Array.to_list (g#pvs_full ()) in
285   fun dev ->
286     try
287       let fs = g#vfs_type dev in
288       if fs = "unknown" then
289         ContentUnknown
290       else if fs = "LVM2_member" then (
291         let rec loop = function
292           | [] ->
293               error "%s: physical volume not returned by pvs_full"
294                 dev
295           | pv :: _ when canonicalize pv.G.pv_name = dev ->
296               ContentPV pv.G.pv_size
297           | _ :: pvs -> loop pvs
298         in
299         loop pvs_full
300       )
301       else (
302         g#mount_ro dev "/";
303         let stat = g#statvfs "/" in
304         let size = stat.G.bsize *^ stat.G.blocks in
305         ContentFS (fs, size)
306       )
307     with
308       G.Error _ -> ContentUnknown
309
310 let partitions : partition list =
311   let parts = Array.to_list (g#part_list "/dev/sda") in
312
313   if List.length parts = 0 then
314     error "the source disk has no partitions";
315
316   let partitions =
317     List.map (
318       fun ({ G.part_num = part_num } as part) ->
319         let part_num = Int32.to_int part_num in
320         let name = sprintf "/dev/sda%d" part_num in
321         let bootable = g#part_get_bootable "/dev/sda" part_num in
322         let mbr_id =
323           try Some (g#part_get_mbr_id "/dev/sda" part_num)
324           with G.Error _ -> None in
325         let typ = get_partition_content name in
326
327         { p_name = name; p_part = part;
328           p_bootable = bootable; p_mbr_id = mbr_id; p_type = typ;
329           p_operation = OpCopy; p_target_partnum = 0;
330           p_target_start = 0L; p_target_end = 0L }
331     ) parts in
332
333   if debug then (
334     eprintf "%d partitions found\n" (List.length partitions);
335     List.iter debug_partition partitions
336   );
337
338   (* Check content isn't larger than partitions.  If it is then
339    * something has gone wrong and we shouldn't continue.  Old
340    * virt-resize didn't do these checks.
341    *)
342   List.iter (
343     function
344     | { p_name = name; p_part = { G.part_size = size };
345         p_type = ContentPV pv_size }
346         when size < pv_size ->
347         error "%s: partition size %Ld < physical volume size %Ld"
348           name size pv_size
349     | { p_name = name; p_part = { G.part_size = size };
350         p_type = ContentFS (_, fs_size) }
351         when size < fs_size ->
352         error "%s: partition size %Ld < filesystem size %Ld"
353           name size fs_size
354     | _ -> ()
355   ) partitions;
356
357   (* Check partitions don't overlap. *)
358   let rec loop end_of_prev = function
359     | [] -> ()
360     | { p_name = name; p_part = { G.part_start = part_start } } :: _
361         when end_of_prev > part_start ->
362         error "%s: this partition overlaps the previous one" name
363     | { p_part = { G.part_end = part_end } } :: parts -> loop part_end parts
364   in
365   loop 0L partitions;
366
367   partitions
368
369 (* Build a data structure describing LVs on the source disk.
370  * This is only used if the user gave the --lv-expand option.
371  *)
372 type logvol = {
373   lv_name : string;
374   lv_type : logvol_content;
375   mutable lv_operation : logvol_operation
376 }
377 and logvol_content = partition_content (* except ContentPV cannot occur *)
378 and logvol_operation =
379   | LVOpNone                     (* nothing *)
380   | LVOpExpand                   (* expand it *)
381
382 let debug_logvol lv =
383   eprintf "%s:\n" lv.lv_name;
384   eprintf "\tcontent: %s\n" (string_of_partition_content lv.lv_type)
385
386 let lvs =
387   let lvs = Array.to_list (g#lvs ()) in
388
389   let lvs = List.map (
390     fun name ->
391       let typ = get_partition_content name in
392       assert (match typ with ContentPV _ -> false | _ -> true);
393
394       { lv_name = name; lv_type = typ; lv_operation = LVOpNone }
395   ) lvs in
396
397   if debug then (
398     eprintf "%d logical volumes found\n" (List.length lvs);
399     List.iter debug_logvol lvs
400   );
401
402   lvs
403
404 (* These functions tell us if we know how to expand the content of
405  * a particular partition or LV, and what method to use.
406  *)
407 type expand_content_method =
408   | PVResize | Resize2fs | NTFSResize | BtrfsFilesystemResize
409
410 let string_of_expand_content_method = function
411   | PVResize -> "pvresize"
412   | Resize2fs -> "resize2fs"
413   | NTFSResize -> "ntfsresize"
414   | BtrfsFilesystemResize -> "btrfs-filesystem-resize"
415
416 let can_expand_content =
417   if expand_content then
418     function
419     | ContentUnknown -> false
420     | ContentPV _ -> true
421     | ContentFS (("ext2"|"ext3"|"ext4"), _) -> true
422     | ContentFS (("ntfs"), _) when !ntfs_available -> true
423     | ContentFS (("btrfs"), _) when !btrfs_available -> true
424     | ContentFS (_, _) -> false
425   else
426     fun _ -> false
427
428 let expand_content_method =
429   if expand_content then
430     function
431     | ContentUnknown -> assert false
432     | ContentPV _ -> PVResize
433     | ContentFS (("ext2"|"ext3"|"ext4"), _) -> Resize2fs
434     | ContentFS (("ntfs"), _) when !ntfs_available -> NTFSResize
435     | ContentFS (("btrfs"), _) when !btrfs_available -> BtrfsFilesystemResize
436     | ContentFS (_, _) -> assert false
437   else
438     fun _ -> assert false
439
440 (* Helper function to locate a partition given what the user might
441  * type on the command line.  It also gives errors for partitions
442  * that the user has asked to be ignored or deleted.
443  *)
444 let find_partition =
445   let hash = Hashtbl.create 13 in
446   List.iter (fun ({ p_name = name } as p) -> Hashtbl.add hash name p)
447     partitions;
448   fun ~option name ->
449     let name =
450       if String.length name < 5 || String.sub name 0 5 <> "/dev/" then
451         "/dev/" ^ name
452       else
453         name in
454     let name = canonicalize name in
455
456     let partition =
457       try Hashtbl.find hash name
458       with Not_found ->
459         error "%s: partition not found in the source disk image (this error came from '%s' option on the command line).  Try running this command: virt-filesystems --partitions --long -a %s"
460           name option infile in
461
462     if partition.p_operation = OpIgnore then
463       error "%s: partition already ignored, you cannot use it in '%s' option"
464         name option;
465
466     if partition.p_operation = OpDelete then
467       error "%s: partition already deleted, you cannot use it in '%s' option"
468         name option;
469
470     partition
471
472 (* Handle --ignore option. *)
473 let () =
474   List.iter (
475     fun dev ->
476       let p = find_partition ~option:"--ignore" dev in
477       p.p_operation <- OpIgnore
478   ) ignores
479
480 (* Handle --delete option. *)
481 let () =
482   List.iter (
483     fun dev ->
484       let p = find_partition ~option:"--delete" dev in
485       p.p_operation <- OpDelete
486   ) deletes
487
488 (* Helper function to mark a partition for resizing.  It prevents the
489  * user from trying to mark the same partition twice.  If the force
490  * flag is given, then we will allow the user to shrink the partition
491  * even if we think that would destroy the content.
492  *)
493 let mark_partition_for_resize ~option ?(force = false) p newsize =
494   let name = p.p_name in
495   let oldsize = p.p_part.G.part_size in
496
497   (match p.p_operation with
498    | OpResize _ ->
499        error "%s: this partition has already been marked for resizing"
500          name
501    | OpIgnore | OpDelete ->
502        (* This error should have been caught already by find_partition ... *)
503        error "%s: this partition has already been ignored or deleted"
504          name
505    | OpCopy -> ()
506   );
507
508   (* Only do something if the size will change. *)
509   if oldsize <> newsize then (
510     let bigger = newsize > oldsize in
511
512     if not bigger && not force then (
513       (* Check if this contains filesystem content, and how big that is
514        * and whether we will destroy any content by shrinking this.
515        *)
516       match p.p_type with
517       | ContentUnknown ->
518           error "%s: This partition has unknown content which might be damaged by shrinking it.  If you want to shrink this partition, you need to use the '--resize-force' option, but that could destroy any data on this partition.  (This error came from '%s' option on the command line.)"
519             name option
520       | ContentPV size when size > newsize ->
521           error "%s: This partition has contains an LVM physical volume which will be damaged by shrinking it below %Ld bytes (user asked to shrink it to %Ld bytes).  If you want to shrink this partition, you need to use the '--resize-force' option, but that could destroy any data on this partition.  (This error came from '%s' option on the command line.)"
522             name size newsize option
523       | ContentPV _ -> ()
524       | ContentFS (fstype, size) when size > newsize ->
525           error "%s: This partition has contains a %s filesystem which will be damaged by shrinking it below %Ld bytes (user asked to shrink it to %Ld bytes).  If you want to shrink this partition, you need to use the '--resize-force' option, but that could destroy any data on this partition.  (This error came from '%s' option on the command line.)"
526             name fstype size newsize option
527       | ContentFS _ -> ()
528     );
529
530     p.p_operation <- OpResize newsize
531   )
532
533 (* Handle --resize and --resize-force options. *)
534 let () =
535   let do_resize ~option ?(force = false) arg =
536     (* Argument is "dev=size". *)
537     let dev, sizefield =
538       try
539         let i = String.index arg '=' in
540         let n = String.length arg - (i+1) in
541         if n == 0 then raise Not_found;
542         String.sub arg 0 i, String.sub arg (i+1) n
543       with Not_found ->
544         error "%s: missing size field in '%s' option" arg option in
545
546     let p = find_partition ~option dev in
547
548     (* Parse the size field. *)
549     let oldsize = p.p_part.G.part_size in
550     let newsize = parse_size oldsize sizefield in
551
552     if newsize <= 0L then
553       error "%s: new partition size is zero or negative" dev;
554
555     mark_partition_for_resize ~option ~force p newsize
556   in
557
558   List.iter (do_resize ~option:"--resize") resizes;
559   List.iter (do_resize ~option:"--resize-force" ~force:true) resizes_force
560
561 (* Helper function calculates the surplus space, given the total
562  * required so far for the current partition layout, compared to
563  * the size of the target disk.  If the return value >= 0 then it's
564  * a surplus, if it is < 0 then it's a deficit.
565  *)
566 let calculate_surplus () =
567   (* We need some overhead for partitioning.  Worst case would be for
568    * EFI partitioning + massive per-partition alignment.
569    *)
570   let nr_partitions = List.length partitions in
571   let overhead = (Int64.of_int sectsize) *^ (
572     2L *^ 64L +^                                 (* GPT start and end *)
573     (128L *^ (Int64.of_int (nr_partitions + 1))) (* Maximum alignment *)
574   ) +^
575   (Int64.of_int (max_bootloader - 64 * 512)) in  (* Bootloader *)
576
577   let required = List.fold_left (
578     fun total p ->
579       let newsize =
580         match p.p_operation with
581         | OpCopy | OpIgnore -> p.p_part.G.part_size
582         | OpDelete -> 0L
583         | OpResize newsize -> newsize in
584       total +^ newsize
585   ) 0L partitions in
586
587   outsize -^ (required +^ overhead)
588
589 (* Handle --expand and --shrink options. *)
590 let () =
591   if expand <> None && shrink <> None then
592     error "you cannot use options --expand and --shrink together";
593
594   if expand <> None || shrink <> None then (
595     let surplus = calculate_surplus () in
596
597     if debug then
598       eprintf "surplus before --expand or --shrink: %Ld\n" surplus;
599
600     (match expand with
601      | None -> ()
602      | Some dev ->
603          if surplus < 0L then
604            error "You cannot use --expand when there is no surplus space to expand into.  You need to make the target disk larger by at least %s."
605              (human_size (Int64.neg surplus));
606
607          let option = "--expand" in
608          let p = find_partition ~option dev in
609          let oldsize = p.p_part.G.part_size in
610          mark_partition_for_resize ~option p (oldsize +^ surplus)
611     );
612     (match shrink with
613      | None -> ()
614      | Some dev ->
615          if surplus > 0L then
616            error "You cannot use --shrink when there is no deficit (see 'deficit' in the virt-resize(1) man page).";
617
618          let option = "--shrink" in
619          let p = find_partition ~option dev in
620          let oldsize = p.p_part.G.part_size in
621          mark_partition_for_resize ~option p (oldsize +^ surplus)
622     )
623   )
624
625 (* Calculate the final surplus.
626  * At this point, this number must be >= 0.
627  *)
628 let surplus =
629   let surplus = calculate_surplus () in
630
631   if surplus < 0L then (
632     let deficit = Int64.neg surplus in
633     error "There is a deficit of %Ld bytes (%s).  You need to make the target disk larger by at least this amount or adjust your resizing requests."
634       deficit (human_size deficit)
635   );
636
637   surplus
638
639 (* Mark the --lv-expand LVs. *)
640 let () =
641   let hash = Hashtbl.create 13 in
642   List.iter (fun ({ lv_name = name } as lv) -> Hashtbl.add hash name lv) lvs;
643
644   List.iter (
645     fun name ->
646       let lv =
647         try Hashtbl.find hash name
648         with Not_found ->
649           error "%s: logical volume not found in the source disk image (this error came from '--lv-expand' option on the command line).  Try running this command: virt-filesystems --logical-volumes --long -a %s"
650             name infile in
651       lv.lv_operation <- LVOpExpand
652   ) lv_expands
653
654 (* Print a summary of what we will do. *)
655 let () =
656   flush stderr;
657
658   if not quiet then (
659     printf "**********\n\n";
660     printf "Summary of changes:\n\n";
661
662     List.iter (
663       fun ({ p_name = name; p_part = { G.part_size = oldsize }} as p) ->
664         let text =
665           match p.p_operation with
666           | OpCopy ->
667               sprintf "%s: This partition will be left alone." name
668           | OpIgnore ->
669               sprintf "%s: This partition will be created, but the contents will be ignored (ie. not copied to the target)." name
670           | OpDelete ->
671               sprintf "%s: This partition will be deleted." name
672           | OpResize newsize ->
673               sprintf "%s: This partition will be resized from %s to %s."
674                 name (human_size oldsize) (human_size newsize) ^
675               if can_expand_content p.p_type then (
676                 sprintf "  The %s on %s will be expanded using the '%s' method."
677                   (string_of_partition_content_no_size p.p_type)
678                   name
679                   (string_of_expand_content_method
680                      (expand_content_method p.p_type))
681               ) else "" in
682
683         wrap ~hanging:4 (text ^ "\n\n")
684     ) partitions;
685
686     List.iter (
687       fun ({ lv_name = name } as lv) ->
688         match lv.lv_operation with
689         | LVOpNone -> ()
690         | LVOpExpand ->
691             let text =
692               sprintf "%s: This logical volume will be expanded to maximum size."
693                 name ^
694               if can_expand_content lv.lv_type then (
695                 sprintf "  The %s on %s will be expanded using the '%s' method."
696                   (string_of_partition_content_no_size lv.lv_type)
697                   name
698                   (string_of_expand_content_method
699                      (expand_content_method lv.lv_type))
700               ) else "" in
701
702             wrap ~hanging:4 (text ^ "\n\n")
703     ) lvs;
704
705     if surplus > 0L then (
706       let text =
707         sprintf "There is a surplus of %s." (human_size surplus) ^
708         if extra_partition then (
709           if surplus >= min_extra_partition then
710             sprintf "  An extra partition will be created for the surplus."
711           else
712             sprintf "  The surplus space is not large enough for an extra partition to be created and so it will just be ignored."
713         ) else
714           sprintf "  The surplus space will be ignored.  Run a partitioning program in the guest to partition this extra space if you want." in
715
716       wrap (text ^ "\n\n")
717     );
718
719     printf "**********\n";
720     flush stdout
721   );
722
723   if dryrun then exit 0
724
725 (* Create a partition table.
726  *
727  * We *must* do this before copying the bootloader across, and copying
728  * the bootloader must be careful not to disturb this partition table
729  * (RHBZ#633766).  There are two reasons for this:
730  *
731  * (1) The 'parted' library is stupid and broken.  In many ways.  In
732  * this particular instance the stupid and broken bit is that it
733  * overwrites the whole boot sector when initializating a partition
734  * table.  (Upstream don't consider this obvious problem to be a bug).
735  *
736  * (2) GPT has a backup partition table located at the end of the disk.
737  * It's non-movable, because the primary GPT contains fixed references
738  * to both the size of the disk and the backup partition table at the
739  * end.  This would be a problem for any resize that didn't either
740  * carefully move the backup GPT (and rewrite those references) or
741  * recreate the whole partition table from scratch.
742  *)
743 let g, parttype =
744   let parttype = g#part_get_parttype "/dev/sda" in
745   if debug then eprintf "partition table type: %s\n%!" parttype;
746
747   (* Try hard to initialize the partition table.  This might involve
748    * relaunching another handle.
749    *)
750   if not quiet then
751     printf "Setting up initial partition table on %s ...\n%!" outfile;
752
753   let last_error = ref "" in
754   let rec initialize_partition_table g attempts =
755     let ok =
756       try g#part_init "/dev/sdb" parttype; true
757       with G.Error error -> last_error := error; false in
758     if ok then g, true
759     else if attempts > 0 then (
760       g#zero "/dev/sdb";
761       g#sync ();
762       g#close ();
763
764       let g = connect_both_disks () in
765       initialize_partition_table g (attempts-1)
766     )
767     else g, false
768   in
769
770   let g, ok = initialize_partition_table g 5 in
771   if not ok then
772     error "Failed to initialize the partition table on the target disk.  You need to wipe or recreate the target disk and then run virt-resize again.\n\nThe underlying error was: %s" !last_error;
773
774   g, parttype
775
776 (* Copy the bootloader across.
777  * Don't disturb the partition table that we just wrote.
778  * https://secure.wikimedia.org/wikipedia/en/wiki/Master_Boot_Record
779  * https://secure.wikimedia.org/wikipedia/en/wiki/GUID_Partition_Table
780  *)
781 let () =
782   if copy_boot_loader then (
783     let bootsect = g#pread_device "/dev/sda" 446 0L in
784     if String.length bootsect < 446 then
785       error "pread-device: short read";
786     ignore (g#pwrite_device "/dev/sdb" bootsect 0L);
787
788     let start =
789       if parttype <> "gpt" then 512L
790       else
791         (* XXX With 4K sectors does GPT just fit more entries in a
792          * sector, or does it always use 34 sectors?
793          *)
794         17408L in
795
796     let loader = g#pread_device "/dev/sda" max_bootloader start in
797     if String.length loader < max_bootloader then
798       error "pread-device: short read";
799     ignore (g#pwrite_device "/dev/sdb" loader start)
800   )
801
802 (* Repartition the target disk. *)
803
804 (* Calculate the location of the partitions on the target disk.  This
805  * also removes from the list any partitions that will be deleted, so
806  * the final list just contains partitions that need to be created
807  * on the target.
808  *)
809 let partitions =
810   let sectsize = Int64.of_int sectsize in
811
812   let rec loop partnum start = function
813     | p :: ps ->
814       (match p.p_operation with
815        | OpDelete -> loop partnum start ps      (* skip p *)
816
817        | OpIgnore | OpCopy ->           (* same size *)
818          (* Size in sectors. *)
819          let size = (p.p_part.G.part_size +^ sectsize -^ 1L) /^ sectsize in
820          (* Start of next partition + alignment. *)
821          let end_ = start +^ size in
822          let next = (end_ +^ 127L) &^ (~^ 127L) in
823
824          { p with p_target_start = start; p_target_end = end_ -^ 1L;
825            p_target_partnum = partnum } :: loop (partnum+1) next ps
826
827        | OpResize newsize ->            (* resized partition *)
828          (* New size in sectors. *)
829          let size = (newsize +^ sectsize -^ 1L) /^ sectsize in
830          (* Start of next partition + alignment. *)
831          let next = start +^ size in
832          let next = (next +^ 127L) &^ (~^ 127L) in
833
834          { p with p_target_start = start; p_target_end = next -^ 1L;
835            p_target_partnum = partnum } :: loop (partnum+1) next ps
836       )
837
838     | [] ->
839       (* Create the surplus partition if there is room for it. *)
840       if extra_partition && surplus >= min_extra_partition then (
841         [ {
842           (* Since this partition has no source, this data is
843            * meaningless and not used since the operation is
844            * OpIgnore.
845            *)
846           p_name = "";
847           p_part = { G.part_num = 0l; part_start = 0L; part_end = 0L;
848                      part_size = 0L };
849           p_bootable = false; p_mbr_id = None; p_type = ContentUnknown;
850
851           (* Target information is meaningful. *)
852           p_operation = OpIgnore;
853           p_target_partnum = partnum;
854           p_target_start = start; p_target_end = ~^ 64L
855         } ]
856       )
857       else
858         []
859   in
860
861   (* The first partition must start at the same position as the old
862    * first partition.  Old virt-resize used to align this to 64
863    * sectors, but I suspect this is the cause of boot failures, so
864    * let's not do this.
865    *)
866   let start = (List.hd partitions).p_part.G.part_start /^ sectsize in
867   loop 1 start partitions
868
869 (* Now partition the target disk. *)
870 let () =
871   List.iter (
872     fun p ->
873       g#part_add "/dev/sdb" "primary" p.p_target_start p.p_target_end;
874
875       (* Set bootable and MBR IDs *)
876       if p.p_bootable then
877         g#part_set_bootable "/dev/sdb" p.p_target_partnum true;
878
879       (match p.p_mbr_id with
880       | None -> ()
881       | Some mbr_id ->
882         g#part_set_mbr_id "/dev/sdb" p.p_target_partnum mbr_id
883       );
884   ) partitions
885
886 (* Copy over the data. *)
887 let () =
888   List.iter (
889     fun p ->
890       match p.p_operation with
891       | OpCopy | OpResize _ ->
892         (* XXX Old code had 'when target_partnum > 0', but it appears
893          * to have served no purpose since the field could never be 0
894          * at this point.
895          *)
896
897         let oldsize = p.p_part.G.part_size in
898         let newsize =
899           match p.p_operation with OpResize s -> s | _ -> oldsize in
900
901         let copysize = if newsize < oldsize then newsize else oldsize in
902
903         let source = p.p_name in
904         let target = sprintf "/dev/sdb%d" p.p_target_partnum in
905
906         if not quiet then
907           printf "Copying %s ...\n%!" source;
908
909         g#copy_size source target copysize;
910
911       | _ -> ()
912   ) partitions
913
914 (* After copying the data over we must shut down and restart the
915  * appliance in order to expand the content.  The reason for this may
916  * not be obvious, but it's because otherwise we'll have duplicate VGs
917  * (the old VG(s) and the new VG(s)) which breaks LVM.
918  *
919  * The restart is only required if we're going to expand something.
920  *)
921 let to_be_expanded =
922   List.exists (
923     function
924     | ({ p_operation = OpResize _ } as p) -> can_expand_content p.p_type
925     | _ -> false
926   ) partitions
927   || List.exists (
928     function
929     | ({ lv_operation = LVOpExpand } as lv) -> can_expand_content lv.lv_type
930     | _ -> false
931   ) lvs
932
933 let g =
934   if to_be_expanded then (
935     g#umount_all ();
936     g#sync ();
937     g#close ();
938
939     let g = new G.guestfs () in
940     if debug then g#set_trace true;
941     g#add_drive_opts ?format:output_format ~readonly:false outfile;
942     if not quiet then Progress.set_up_progress_bar ~machine_readable g;
943     g#launch ();
944
945     g (* Return new handle. *)
946   )
947   else g (* Return existing handle. *)
948
949 let () =
950   if to_be_expanded then (
951     (* Helper function to expand partition or LV content. *)
952     let do_expand_content target = function
953       | PVResize -> g#pvresize target
954       | Resize2fs ->
955           g#e2fsck_f target;
956           g#resize2fs target
957       | NTFSResize -> g#ntfsresize_opts ~force:ntfsresize_force target
958       | BtrfsFilesystemResize ->
959           (* Complicated ...  Btrfs forces us to mount the filesystem
960            * in order to resize it.
961            *)
962           assert (Array.length (g#mounts ()) = 0);
963           g#mount_options "" target "/";
964           g#btrfs_filesystem_resize "/";
965           g#umount "/"
966     in
967
968     (* Expand partition content as required. *)
969     List.iter (
970       function
971       | ({ p_operation = OpResize _ } as p) when can_expand_content p.p_type ->
972           let source = p.p_name in
973           let target = sprintf "/dev/sda%d" p.p_target_partnum in
974           let meth = expand_content_method p.p_type in
975
976           if not quiet then
977             printf "Expanding %s%s using the '%s' method ...\n%!"
978               source
979               (if source <> target then sprintf " (now %s)" target else "")
980               (string_of_expand_content_method meth);
981
982           do_expand_content target meth
983       | _ -> ()
984     ) partitions;
985
986     (* Expand logical volume content as required. *)
987     List.iter (
988       function
989       | ({ lv_operation = LVOpExpand } as lv) when can_expand_content lv.lv_type ->
990           let name = lv.lv_name in
991           let meth = expand_content_method lv.lv_type in
992
993           if not quiet then
994             printf "Expanding %s using the '%s' method ...\n%!"
995               name
996               (string_of_expand_content_method meth);
997
998           (* First expand the LV itself to maximum size. *)
999           g#lvresize_free name 100;
1000
1001           (* Then expand the content in the LV. *)
1002           do_expand_content name meth
1003       | _ -> ()
1004     ) lvs
1005   )
1006
1007 (* Finished.  Unmount disks and exit. *)
1008 let () =
1009   g#umount_all ();
1010   g#sync ();
1011   g#close ();
1012
1013   if not quiet then (
1014     print_newline ();
1015     wrap "Resize operation completed with no errors.  Before deleting the old disk, carefully check that the resized disk boots and works correctly.\n";
1016   );
1017
1018   exit 0