summaryrefslogtreecommitdiffstats
path: root/perl-install/interactive_gtk.pm
blob: c0582ea5174b8992dd15d5205aa6866101d6415c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
package interactive_gtk;

use diagnostics;
use strict;
use vars qw(@ISA);

@ISA = qw(interactive);

use interactive;
use common qw(:common :functional);
use my_gtk qw(:helpers :wrappers);

1;

## redefine ask_warn
#sub ask_warn {
#    my $o = shift;
#    local $my_gtk::grab = 1;
#    $o->SUPER::ask_warn(@_);
#}

sub ask_from_entryW {
    my ($o, $title, $messages, $def) = @_;
    my $w = my_gtk->new($title, %$o);
    $w->_ask_from_entry(@$messages);
    $w->main;
}
sub ask_from_listW {
    my ($o, $title, $messages, $l, $def) = @_;

    if (@$l < 5 && sum(map { length $_ } @$l) < 70) {
	my $defW;
	my $w = my_gtk->new($title, %$o);
	my $f = sub { $w->{retval} = $_[1]; Gtk->main_quit };
	gtkadd($w->{window},
	       gtkpack(create_box_with_title($w, @$messages),
		       gtkadd((@$l < 3 ? create_hbox() : create_vbox()),
			      map {
				  my $b = new Gtk::Button($_);
				  $b->signal_connect(clicked => [ $f, $_ ]);
				  $_ eq $def and $defW = $b;
				  $b;
			      } @$l),
		       ),
	       );
	$defW->grab_focus if $defW;
	$w->main;
    } else {
	my $w = my_gtk->new($title);
	$w->_ask_from_list($messages, $l, $def);
	$w->main;
    }
}

sub ask_many_from_list_refW($$$$$) {
    my ($o, $title, $messages, $list, $val) = @_;
    my $n = 0;
    my $w = my_gtk->new('', %$o);
    gtkadd($w->{window}, 
	   gtkpack(create_box_with_title($w, @$messages),
		   gtkpack(new Gtk::VBox(0,0),
			   map { 
			       my $nn = $n++; 
			       my $o = Gtk::CheckButton->new($_);
			       $o->set_active(${$val->[$nn]});
			       $o->signal_connect(clicked => sub { ${$val->[$nn]} = !${$val->[$nn]} });
			       $o;
			   } @$list),
		   $w->create_okcancel,
		  )
	  );
    $w->{ok}->grab_focus;
    $w->main && $val;
}


sub ask_from_entries_refW {
    my ($o, $title, $messages, $l, $val, %hcallback) = @_;
    my $num_fields = @{$l};
    my $ignore = 0; #to handle recursivity 

    my $w       = my_gtk->new($title, %$o);
    #the widgets
    my @entries = map { 
	if ($_->{type} eq "list") {
	    my $depth_combo = new Gtk::Combo;
	    $depth_combo->set_use_arrows_always(1);
	    $depth_combo->entry->set_editable(!$_->{not_edit});
	    $depth_combo->set_popdown_strings(@{$_->{list}});
	    $depth_combo->disable_activate;
	    $depth_combo;
	} else {
	    new Gtk::Entry;
	}
    } @{$val};
    my $ok      = $w->create_okcancel;
    sub comb_entry {
	my ($entry, $ref) = @_;
	($ref->{type} eq "list" && @{$ref->{list}}) ? $entry->entry : $entry
    }

    my @updates = mapn { 
	my ($entry, $ref) = @_;
	sub { ${$ref->{val}} = comb_entry($entry, $ref)->get_text };
    } \@entries, $val;

    my @updates_inv = mapn { 
	my ($entry, $ref) = @_;
	sub { comb_entry($entry, $ref)->set_text(${$ref->{val}})
	};
    } \@entries, $val;


    for (my $i = 0; $i < $num_fields; $i++) {
	my $ind = $i; #cos lexical bindings pb !!
	my $entry = $entries[$i];
	#changed callback
	my $callback = sub {
	    return if $ignore; #handle recursive deadlock
	    &{$updates[$ind]};
	    if ($hcallback{changed}) {
		&{$hcallback{changed}}($ind);
		#update all the value
		$ignore = 1;
		&$_ foreach @updates_inv;
		$ignore = 0;
	    };
	};
	if ($hcallback{focus_out}) {
	    my $callfocusout = sub {
		return if $ignore;
		&{$hcallback{focus_out}}($ind);
		#update all the value
		$ignore = 1;
		foreach (@updates_inv) { &{$_};}
		$ignore = 0;
	    };
	    comb_entry($entry,$val->[$i])->signal_connect(focus_out_event => $callfocusout);
	}
	comb_entry($entry,$val->[$i])->signal_connect(changed => $callback);
	comb_entry($entry,$val->[$i])->signal_connect(activate => sub {
				   ($ind == ($num_fields -1)) ?
				     ($w->{ok}->grab_focus(), ) : (comb_entry($entries[$ind+1],$val->[$ind+1])->grab_focus(),$_[0]->signal_emit_stop("activate")) ;
			       });
	comb_entry($entry,$val->[$i])->set_text(${$val->[$i]{val}})  if ${$val->[$i]{val}};
	comb_entry($entry,$val->[$i])->set_visibility(0) if $l->[$i] =~ /password/i;
#	&{$updates[$i]};
    }

    my @entry_list = mapn { [($_[0], $_[1])]} $l, \@entries;

    gtkadd($w->{window}, 
	   gtkpack(
		   create_box_with_title($w, @$messages),
		   create_packtable({}, @entry_list),
		   $ok
		   ));

    comb_entry($entries[0],$val->[0])->grab_focus();
    if ($hcallback{complete}) {
	my $callback = sub {
	    my ($error, $focus) = &{$hcallback{complete}};
	    #update all the value
	    $ignore = 1;
	    foreach (@updates_inv) { &{$_};}
	    $ignore = 0;
	    if ($error) {
		comb_entry($entries[$focus], $val->[$focus])->grab_focus();
	    } else {
		return 1;
	    }
	};
	#$w->{ok}->signal_connect(clicked => $callback)
	$w->main($callback);
    } else {
	$w->main();
    }


}


sub wait_messageW($$$) {
    my ($o, $title, $message) = @_;

    my $w = my_gtk->new(_("Resizing"), %$o, grab => 1);
    my $W = pop @$message;
    gtkadd($w->{window}, 
	   gtkpack(new Gtk::VBox(0,0), 
		   @$message, 
		   $w->{wait_messageW} = new Gtk::Label($W)));
    $w->sync;
    $w;
}
sub wait_message_nextW {
    my ($o, $message, $w) = @_;
    $w->{wait_messageW}->set($message);
    $w->sync;
}
sub wait_message_endW {
    my ($o, $w) = @_;
    $w->destroy;
}
n class="hl num">0x75 => 'IBM PC/IX', 0x80 => 'MINIX until 1.4a', 0x81 => 'MINIX since 1.4b, early Linux / Mitac disk manager', 0x82 => 'Linux swap', 0x83 => 'Linux native', 0x84 => 'OS/2 hidden C: drive / Hibernation partition', 0x85 => 'Linux extended partition', 0x86 => 'Old Linux RAID partition superblock / NTFS volume set', 0x87 => 'NTFS volume set', 0x8a => 'Linux Kernel Partition (used by AiR-BOOT)', 0x8e => 'Linux Logical Volume Manager partition', 0x93 => 'Amoeba', 0x94 => 'Amoeba bad block table', 0x99 => 'DCE376 logical drive', 0xa0 => 'IBM Thinkpad hibernation partition / Phoenix NoteBIOS Power Management "Save-to-Disk" partition', 0xa5 => 'BSD/386, 386BSD, NetBSD, FreeBSD', 0xa6 => 'OpenBSD', 0xa7 => 'NEXTSTEP', 0xa9 => 'NetBSD', 0xaa => 'Olivetti Fat 12 1.44Mb Service Partition', 0xb7 => 'BSDI filesystem', 0xb8 => 'BSDI swap partition', 0xbe => 'Solaris boot partition', 0xc0 => 'CTOS / REAL/32 secure small partition', 0xc1 => 'DRDOS/secured (FAT-12)', 0xc4 => 'DRDOS/secured (FAT-16, < 32M)', 0xc6 => 'DRDOS/secured (FAT-16, >= 32M) / Windows NT corrupted FAT16 volume/stripe set', 0xc7 => 'Windows NT corrupted NTFS volume/stripe set / Syrinx boot', 0xcb => 'reserved for DRDOS/secured (FAT32)', 0xcc => 'reserved for DRDOS/secured (FAT32, LBA)', 0xcd => 'CTOS Memdump?', 0xce => 'reserved for DRDOS/secured (FAT16, LBA)', 0xd0 => 'REAL/32 secure big partition', 0xd1 => 'Old Multiuser DOS secured FAT12', 0xd4 => 'Old Multiuser DOS secured FAT16 <32M', 0xd5 => 'Old Multiuser DOS secured extended partition', 0xd6 => 'Old Multiuser DOS secured FAT16 >=32M', 0xd8 => 'CP/M-86', 0xdb => 'Digital Research CP/M, Concurrent CP/M, Concurrent DOS / CTOS (Convergent Technologies OS -Unisys) / KDG Telemetry SCPU boot', 0xdd => 'Hidden CTOS Memdump?', 0xe1 => 'DOS access or SpeedStor 12-bit FAT extended partition', 0xe3 => 'DOS R/O or SpeedStor', 0xe4 => 'SpeedStor 16-bit FAT extended partition < 1024 cyl.', 0xeb => 'BeOS', 0xee => 'Indication that this legacy MBR is followed by an EFI header', 0xef => 'Partition that contains an EFI file system', 0xf1 => 'SpeedStor', 0xf2 => 'DOS 3.3+ secondary partition', 0xf4 => 'SpeedStor large partition / Prologue single-volume partition', 0xf5 => 'Prologue multi-volume partition', 0xfd => 'Linux RAID', 0xfe => 'SpeedStor > 1024 cyl. or LANstep / IBM PS/2 IML (Initial Microcode Load) partition, located at the end of the disk. / Windows NT Disk Administrator hidden partition / Linux Logical Volume Manager partition (old)', 0xff => 'Xenix Bad Block Table', ); my %type2fs = ( arch() !~ /^sparc/ ? ( 0x01 => 'vfat', 0x04 => 'vfat', 0x05 => 'ignore', 0x06 => 'vfat', 0x07 => 'hpfs', ) : (), 0x0b => 'vfat', 0x0c => 'vfat', 0x0e => 'vfat', 0x1b => 'vfat', 0x1c => 'vfat', 0x1e => 'vfat', 0x82 => 'swap', 0x83 => 'ext2', 0x402 => 'hfs', nfs => 'nfs', #- hack ); my %types_rev = reverse %types; my %fs2type = reverse %type2fs; 1; sub important_types { $_[0] and return sort values %types; @important_types } sub type2name($) { $types{$_[0]} || $_[0] } sub type2fs($) { $type2fs{$_[0]} } sub fs2type($) { $fs2type{$_[0]} } sub name2type($) { local ($_) = @_; /0x(.*)/ ? hex $1 : $types_rev{$_} || $_; } sub isWholedisk($) { arch() =~ /^sparc/ && $_[0]{type} == 5 } sub isExtended($) { (arch() !~ /^sparc/ && $_[0]{type} == 5) || $_[0]{type} == 0xf || $_[0]{type} == 0x85 } sub isRAID($) { $_[0]{type} == 0xfd } sub isSwap($) { $type2fs{$_[0]{type}} eq 'swap' } sub isExt2($) { $type2fs{$_[0]{type}} eq 'ext2' } sub isDos($) { $ {{ 1=>1, 4=>1, 6=>1 }}{$_[0]{type}} } sub isWin($) { $ {{ 0xb=>1, 0xc=>1, 0xe=>1, 0x1b=>1, 0x1c=>1, 0x1e=>1 }}{$_[0]{type}} } sub isFat($) { isDos($_[0]) || isWin($_[0]) } sub isNfs($) { $_[0]{type} eq 'nfs' } #- small hack sub isSupermount($) { $_[0]{type} eq 'supermount' } sub isHFS($) { $type2fs{$_[0]{type}} eq 'hfs' } sub isMountableRW { isExt2($_[0]) || isFat($_[0]) } sub isApplePartMap { defined $_[0]{isMap} } sub isLoopback { defined $_[0]{loopback_file} } sub isPrimary($$) { my ($part, $hd) = @_; foreach (@{$hd->{primary}{raw}}) { $part eq $_ and return 1; } 0; } sub adjustStartAndEnd($$) { my ($hd, $part) = @_; $hd->adjustStart($part); $hd->adjustEnd($part); } sub verifyNotOverlap($$) { my ($a, $b) = @_; $a->{start} + $a->{size} <= $b->{start} || $b->{start} + $b->{size} <= $a->{start}; } sub verifyInside($$) { my ($a, $b) = @_; $b->{start} <= $a->{start} && $a->{start} + $a->{size} <= $b->{start} + $b->{size}; } sub verifyParts_ { foreach my $i (@_) { foreach (@_) { next if !$i || !$_ || $i == $_ || isWholedisk($i); #- avoid testing twice on whole disk for simplicity :-) isWholedisk($_) ? verifyInside($i, $_) || cdie sprintf("partitions sector #$i->{start} (%dMB) is not inside whole disk (%dMB)!", $i->{size} >> 11, $_->{size} >> 11) : verifyNotOverlap($i, $_) || cdie sprintf("partitions sector #$i->{start} (%dMB) and sector #$_->{start} (%dMB) are overlapping!", $i->{size} >> 11, $_->{size} >> 11); } } } sub verifyParts($) { my ($hd) = @_; verifyParts_(get_normal_parts($hd)); } sub verifyPrimary($) { my ($pt) = @_; $_->{start} > 0 || arch() =~ /^sparc/ || die "partition must NOT start at sector 0" foreach @{$pt->{normal}}; verifyParts_(@{$pt->{normal}}, $pt->{extended}); } sub assign_device_numbers($) { my ($hd) = @_; my $i = 1; $_->{device} = $hd->{prefix} . $i++ foreach @{$hd->{primary}{raw}}, map { $_->{normal} } @{$hd->{extended} || []}; #- try to figure what the windobe drive letter could be! # #- first verify there's at least one primary dos partition, otherwise it #- means it is a secondary disk and all will be false :( my ($c, @others) = grep { isFat($_) } @{$hd->{primary}{normal}}; $c or return; $i = ord 'D'; foreach (grep { isFat($_) } map { $_->{normal} } @{$hd->{extended}}) { $_->{device_windobe} = chr($i++); } $c->{device_windobe} = 'C'; $_->{device_windobe} = chr($i++) foreach @others; } sub remove_empty_extended($) { my ($hd) = @_; my $last = $hd->{primary}{extended} or return; @{$hd->{extended}} = grep { if ($_->{normal}) { $last = $_; } else { %{$last->{extended}} = $_->{extended} ? %{$_->{extended}} : (); } $_->{normal}; } @{$hd->{extended}}; adjust_main_extended($hd); } sub adjust_main_extended($) { my ($hd) = @_; if (!is_empty_array_ref $hd->{extended}) { my ($l, @l) = @{$hd->{extended}}; # the first is a special case, must recompute its real size my $start = round_down($l->{normal}{start} - 1, $hd->{geom}{sectors}); my $end = $l->{normal}{start} + $l->{normal}{size}; foreach (map $_->{normal}, @l) { $start = min($start, $_->{start}); $end = max($end, $_->{start} + $_->{size}); } $l->{start} = $hd->{primary}{extended}{start} = $start; $l->{size} = $hd->{primary}{extended}{size} = $end - $start; } unless (@{$hd->{extended} || []} || !$hd->{primary}{extended}) { %{$hd->{primary}{extended}} = (); #- modify the raw entry delete $hd->{primary}{extended}; } verifyParts($hd); #- verify everything is all right } sub adjust_local_extended($$) { my ($hd, $part) = @_; foreach (@{$hd->{extended} || []}) { $_->{normal} == $part or next; $_->{size} = $part->{size} + $part->{start} - $_->{start}; last; } } sub get_normal_parts($) { my ($hd) = @_; #- HACK !! $hd->{raid} and return grep {$_} @{$hd->{raid}}; $hd->{loopback} and return grep {$_} @{$hd->{loopback}}; @{$hd->{primary}{normal} || []}, map { $_->{normal} } @{$hd->{extended} || []} } sub get_holes($) { my ($hd) = @_; my $start = 1; map { my $current = $start; $start = $_->{start} + $_->{size}; { start => $current, size => $_->{start} - $current } } sort { $a->{start} <=> $b->{start} } get_normal_parts($hd), { start => $hd->{totalsectors}, size => 0 }; } sub read_one($$) { my ($hd, $sector) = @_; my ($pt, $info); foreach ('dos', 'bsd', 'sun', 'mac', 'unknown') { /unknown/ and die "unknown partition table format"; eval { bless $hd, "partition_table_$_"; ($pt, $info) = $hd->read($sector); }; $@ or last; } my @extended = $hd->hasExtended ? grep { isExtended($_) } @$pt : (); my @normal = grep { $_->{size} && $_->{type} && !isExtended($_) } @$pt; @extended > 1 and die "more than one extended partition"; $_->{rootDevice} = $hd->{device} foreach @normal, @extended; { raw => $pt, extended => $extended[0], normal => \@normal, info => $info }; } sub read($;$) { my ($hd, $clearall) = @_; if ($clearall) { partition_table_raw::zero_MBR($hd); return 1; } my $pt = read_one($hd, 0) or return 0; $hd->{primary} = $pt; undef $hd->{extended}; verifyPrimary($pt); eval { $pt->{extended} and read_extended($hd, $pt->{extended}) || return 0; }; die "extended partition: $@" if $@; assign_device_numbers($hd); remove_empty_extended($hd); 1; } sub read_extended { my ($hd, $extended) = @_; my $pt = read_one($hd, $extended->{start}) or return 0; $pt = { %$extended, %$pt }; push @{$hd->{extended}}, $pt; @{$hd->{extended}} > 100 and die "oops, seems like we're looping here :( (or you have more than 100 extended partitions!)"; @{$pt->{normal}} <= 1 or die "more than one normal partition in extended partition"; @{$pt->{normal}} >= 1 or die "no normal partition in extended partition"; $pt->{normal} = $pt->{normal}[0]; #- in case of extended partitions, the start sector is local to the partition or to the first extended_part! $pt->{normal}{start} += $pt->{start}; #- the following verification can broke an existing partition table that is #- correctly read by fdisk or cfdisk. maybe the extended partition can be #- recomputed to get correct size. if (!verifyInside($pt->{normal}, $extended)) { $extended->{size} = $pt->{normal}{start} + $pt->{normal}{size}; verifyInside($pt->{normal}, $extended) or die "partition $pt->{normal}{device} is not inside its extended partition"; } if ($pt->{extended}) { $pt->{extended}{start} += $hd->{primary}{extended}{start}; read_extended($hd, $pt->{extended}) or return 0; } 1; } # write the partition table sub write($) { my ($hd) = @_; #- set first primary partition active if no primary partitions are marked as active. for ($hd->{primary}{raw}) { (grep { $_->{local_start} = $_->{start}; $_->{active} ||= 0 } @$_) or $_->[0]{active} = 0x80; } #- last chance for verification, this make sure if an error is detected, #- it will never be writed back on partition table. verifyParts($hd); $hd->write(0, $hd->{primary}{raw}, $hd->{primary}{info}) or die "writing of partition table failed"; #- should be fixed but a extended exist with no real extended partition, that blanks mbr! foreach (@{$hd->{extended}}) { # in case of extended partitions, the start sector must be local to the partition $_->{normal}{local_start} = $_->{normal}{start} - $_->{start}; $_->{extended} and $_->{extended}{local_start} = $_->{extended}{start} - $hd->{primary}{extended}{start}; $hd->write($_->{start}, $_->{raw}) or die "writing of partition table failed"; } $hd->{isDirty} = 0; #- now sync disk and re-read the partition table if ($hd->{needKernelReread}) { sync(); $hd->kernel_read; $hd->{needKernelReread} = 0; } } sub active($$) { my ($hd, $part) = @_; $_->{active} = 0 foreach @{$hd->{primary}{normal}}; $part->{active} = 0x80; } # remove a normal partition from hard drive hd sub remove($$) { my ($hd, $part) = @_; my $i; #- first search it in the primary partitions $i = 0; foreach (@{$hd->{primary}{normal}}) { if ($_ eq $part) { splice(@{$hd->{primary}{normal}}, $i, 1); %$_ = (); #- blank it return $hd->{isDirty} = $hd->{needKernelReread} = 1; } $i++; } my ($first, $second, $third) = map { $_->{normal} } @{$hd->{extended} || []}; if ($third && $first eq $part) { die "Can't handle removing hda5 when hda6 is not the second partition" if $second->{start} > $third->{start}; } #- otherwise search it in extended partitions foreach (@{$hd->{extended} || []}) { $_->{normal} eq $part or next; delete $_->{normal}; #- remove it remove_empty_extended($hd); return $hd->{isDirty} = $hd->{needKernelReread} = 1; } 0; } # create of partition at starting at `start', of size `size' and of type `type' (nice comment, uh?) sub add_primary($$) { my ($hd, $part) = @_; { local $hd->{primary}{normal}; #- save it to fake an addition of $part, that way add_primary do not modify $hd if it fails push @{$hd->{primary}{normal}}, $part; adjust_main_extended($hd); #- verify raw_add($hd->{primary}{raw}, $part); } push @{$hd->{primary}{normal}}, $part; #- really do it } sub add_extended($$) { my ($hd, $part) = @_; my $e = $hd->{primary}{extended}; if ($e && !verifyInside($part, $e)) { #-die "sorry, can't add outside the main extended partition" unless $::unsafe; my $end = $e->{start} + $e->{size}; my $start = min($e->{start}, $part->{start}); $end = max($end, $part->{start} + $part->{size}) - $start; { #- faking a resizing of the main extended partition to test for problems local $e->{start} = $start; local $e->{size} = $end - $start; eval { verifyPrimary($hd->{primary}) }; $@ and die _("You have a hole in your partition table but I can't use it. The only solution is to move your primary partitions to have the hole next to the extended partitions"); } } if ($e && $part->{start} < $e->{start}) { my $l = first (@{$hd->{extended}}); #- the first is a special case, must recompute its real size $l->{start} = round_down($l->{normal}{start} - 1, $hd->cylinder_size()); $l->{size} = $l->{normal}{start} + $l->{normal}{size} - $l->{start}; my $ext = { %$l }; unshift @{$hd->{extended}}, { type => 5, raw => [ $part, $ext, {}, {} ], normal => $part, extended => $ext }; #- size will be autocalculated :) } else { my ($ext, $ext_size) = is_empty_array_ref($hd->{extended}) ? ($hd->{primary}, -1) : #- -1 size will be computed by adjust_main_extended (top(@{$hd->{extended}}), $part->{size}); my %ext = ( type => 5, start => $part->{start}, size => $ext_size ); raw_add($ext->{raw}, \%ext); $ext->{extended} = \%ext; push @{$hd->{extended}}, { %ext, raw => [ $part, {}, {}, {} ], normal => $part }; } $part->{start}++; $part->{size}--; #- let it start after the extended partition sector adjustStartAndEnd($hd, $part); adjust_main_extended($hd); } sub add($$;$$) { my ($hd, $part, $primaryOrExtended, $forceNoAdjust) = @_; get_normal_parts($hd) >= ($hd->{device} =~ /^sd/ ? 15 : 63) and cdie "maximum number of partitions handled by linux reached"; $part->{notFormatted} = 1; $part->{isFormatted} = 0; $part->{rootDevice} = $hd->{device}; $hd->{isDirty} = $hd->{needKernelReread} = 1; $part->{start} ||= 1 if arch() !~ /^sparc/; #- starting at sector 0 is not allowed adjustStartAndEnd($hd, $part) unless $forceNoAdjust; my $e = $hd->{primary}{extended}; if ($primaryOrExtended eq 'Primary' || $primaryOrExtended ne 'Extended' && is_empty_array_ref($hd->{primary}{normal})) { eval { add_primary($hd, $part) }; return unless $@; } eval { add_extended($hd, $part) } if $hd->hasExtended; #- try adding extended if ($@ || !$hd->hasExtended) { eval { add_primary($hd, $part) }; die $@ if $@; #- send the add extended error which should be better } } # search for the next partition sub next($$) { my ($hd, $part) = @_; first( sort { $a->{start} <=> $b->{start} } grep { $_->{start} >= $part->{start} + $part->{size} } get_normal_parts($hd) ); } sub next_start($$) { my ($hd, $part) = @_; my $next = &next($hd, $part); $next ? $next->{start} : $hd->{totalsectors}; } sub raw_add($$) { my ($raw, $part) = @_; foreach (@$raw) { $_->{size} || $_->{type} and next; $_ = $part; return; } die "raw_add: partition table already full"; } sub load($$;$) { my ($hd, $file, $force) = @_; local *F; open F, $file or die _("Error reading file %s", $file); my $h; { local $/ = "\0"; eval <F>; } $@ and die _("Restoring from file %s failed: %s", $file, $@); ref $h eq 'ARRAY' or die _("Bad backup file"); my %h; @h{@fields2save} = @$h; $h{totalsectors} == $hd->{totalsectors} or $force or cdie("Bad totalsectors"); #- unsure we don't modify totalsectors local $hd->{totalsectors}; @{$hd}{@fields2save} = @$h; delete @$_{qw(isMounted isFormatted notFormatted toFormat toFormatUnsure)} foreach get_normal_parts($hd); $hd->{isDirty} = $hd->{needKernelReread} = 1; } sub save($$) { my ($hd, $file) = @_; my @h = @{$hd}{@fields2save}; local *F; open F, ">$file" and print F Data::Dumper->Dump([\@h], ['$h']), "\0" or die _("Error writing to file %s", $file); }