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