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