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