summaryrefslogtreecommitdiffstats
path: root/perl-install/loopback.pm
blob: 45505bda4e10c9c6dc777981156fd00631410e1c (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
package loopback; # $Id$

use diagnostics;
use strict;

#-######################################################################################
#- misc imports
#-######################################################################################
use MDK::Common::System;
use common;
use partition_table qw(:types);
use fs;
use fsedit;
use log;


sub carryRootLoopback {
    my ($part) = @_;
    $_->{mntpoint} eq '/' and return 1 foreach @{$part->{loopback} || []};
    0;
}

sub check_circular_mounts {
    my ($_hd, $part, $all_hds) = @_;

    my $fstab = [ fsedit::get_all_fstab($all_hds), $part ]; # no pb if $part is already in $all_hds

    my $base_mntpoint = $part->{mntpoint};
    my $check; $check = sub {
	my ($part, @seen) = @_;
	push @seen, $part->{mntpoint} || return;
	@seen > 1 && $part->{mntpoint} eq $base_mntpoint and die \N("Circular mounts %s\n", join(", ", @seen));
	if (my $part = fs::up_mount_point($part->{mntpoint}, $fstab)) {
	    #- '/' carrier is a special case, it will be mounted first
	    $check->($part, @seen) if !carryRootLoopback($part);
	}
	if (isLoopback($part)) {
	    $check->($part->{loopback_device}, @seen);
	}
    };
    $check->($part) if !($base_mntpoint eq '/' && isLoopback($part)); #- '/' is a special case, no loop check
}

sub carryRootCreateSymlink {
    my ($part, $prefix) = @_;

    carryRootLoopback($part) or return;

    my $mntpoint = "$prefix$part->{mntpoint}";
    unless (-e $mntpoint) {
	eval { mkdir_p(dirname($mntpoint)) };
	#- do non-relative link for install, should be changed to relative link before rebooting
	symlink "/initrd/loopfs", $mntpoint;

	mkdir_p("/initrd/loopfs/lnx4win/boot");
	symlink "/initrd/loopfs/lnx4win/boot", "$prefix/boot";
    }
    #- indicate kernel to keep initrd
    mkdir_p("$prefix/initrd");
}


sub format_part {
    my ($part, $prefix) = @_;
    fs::mount_part($part->{loopback_device}, $prefix);
    create($part, $prefix);
    fs::real_format_part($part);
}

sub create {
    my ($part, $prefix) = @_;
    my $f = $part->{device} = "$prefix$part->{loopback_device}{mntpoint}$part->{loopback_file}";
    return if -e $f;

    eval { mkdir_p(dirname($f)) };

    log::l("creating loopback file $f ($part->{size} sectors)");

    my $block_size = 128;
    my $s = "\0" x (512 * $block_size);
    sysopen(my $F, $f, 2 | c::O_CREAT()) or die "failed to create loopback file";
    for (my $i = 0; $i < $part->{size}; $i += $block_size) {
	syswrite $F, $s or die "failed to create loopback file";
    }
}

sub getFree {
    my ($dir, $part) = @_;
    my $freespace = $dir ? 
      2 * (MDK::Common::System::df($dir))[1] : #- df in KiB
      $part->{size};

    $freespace - sum map { $_->{size} } @{$part->{loopback} || []};
}

#- returns the size of the loopback file if it already exists
#- returns -1 is the loopback file can't be used
sub verifFile {
    my ($dir, $file, $part) = @_;
    -e "$dir$file" and return -s "$dir$file";

    $_->{loopback_file} eq $file and return -1 foreach @{$part->{loopback} || []};

    undef;
}

sub prepare_boot() {
    my $r = readlink "$::prefix/boot"; 
    unlink "$::prefix/boot"; 
    mkdir_p("$::prefix/boot");
    [$r, $::prefix];
}

sub save_boot {
    my ($loop_boot, $prefix) = @{$_[0]};
    
    $loop_boot or return;

    my @files = glob_("$prefix/boot/*");
    cp_af(@files, $loop_boot) if @files;
    rm_rf("$prefix/boot");
    symlink $loop_boot, "$prefix/boot";
}


1;

ref='#n636'>636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818
package fsedit; # $Id$

use diagnostics;
use strict;
use vars qw(%suggestions);

#-######################################################################################
#- misc imports
#-######################################################################################
use common;
use partition_table qw(:types);
use partition_table::raw;
use detect_devices;
use fsedit;
use devices;
use loopback;
use log;
use fs;

%suggestions = (
  N_("simple") => [
    { mntpoint => "/",     size => 300 << 11, type =>0x483, ratio => 5, maxsize => 6000 << 11 },
    { mntpoint => "swap",  size =>  64 << 11, type => 0x82, ratio => 1, maxsize =>  500 << 11 },
    { mntpoint => "/home", size => 300 << 11, type =>0x483, ratio => 3 },
  ], N_("with /usr") => [
    { mntpoint => "/",     size => 250 << 11, type =>0x483, ratio => 1, maxsize => 2000 << 11 },
    { mntpoint => "swap",  size =>  64 << 11, type => 0x82, ratio => 1, maxsize =>  500 << 11 },
    { mntpoint => "/usr",  size => 300 << 11, type =>0x483, ratio => 4, maxsize => 4000 << 11 },
    { mntpoint => "/home", size => 100 << 11, type =>0x483, ratio => 3 },
  ], N_("server") => [
    { mntpoint => "/",     size => 150 << 11, type =>0x483, ratio => 1, maxsize =>  800 << 11 },
    { mntpoint => "swap",  size =>  64 << 11, type => 0x82, ratio => 2, maxsize =>  800 << 11 },
    { mntpoint => "/usr",  size => 300 << 11, type =>0x483, ratio => 4, maxsize => 4000 << 11 },
    { mntpoint => "/var",  size => 200 << 11, type =>0x483, ratio => 3 },
    { mntpoint => "/home", size => 150 << 11, type =>0x483, ratio => 3 },
    { mntpoint => "/tmp",  size => 150 << 11, type =>0x483, ratio => 2, maxsize => 1000 << 11 },
  ],
);
foreach (values %suggestions) {
    if (arch() =~ /ia64/) {
	@$_ = ({ mntpoint => "/boot/efi", size => 50 << 11, type => 0xef, ratio => 1, maxsize => 150 << 11 }, @$_);
    }
}

my @suggestions_mntpoints = (
    "/var/ftp", "/var/www", "/boot",
    arch() =~ /sparc/ ? "/mnt/sunos" : arch() =~ /ppc/ ? "/mnt/macos" : "/mnt/windows",
    #- RedHat also has /usr/local and /opt
);

my @partitions_signatures = (
    [ 0x8e, 0, "HM\1\0" ],
    [ 0x83, 0x438, "\x53\xEF" ],
    [ 0x183, 0x10034, "ReIsErFs" ],
    [ 0x183, 0x10034, "ReIsEr2Fs" ],
    [ 0x283, 0, 'XFSB', 0x200, 'XAGF', 0x400, 'XAGI' ],
    [ 0x383, 0x8000, 'JFS1' ],
    [ 0x82, 4086, "SWAP-SPACE" ],
    [ 0x82, 4086, "SWAPSPACE2" ],
    [ 0x107, 0x1FE, "\x55\xAA", 0x3, "NTFS" ],
    [ 0xc,  0x1FE, "\x55\xAA", 0x52, "FAT32" ],
if_(arch() !~ /^sparc/,
    [ 0x6,  0x1FE, "\x55\xAA", 0x36, "FAT" ],
),
);

sub typeOfPart { 
    my $dev = devices::make($_[0]);
    my $t = typeFromMagic($dev, @partitions_signatures);
    if ($t == 0x83) {
	#- there is no magic to differentiate ext3 and ext2. Using libext2fs
	#- to check if it has a journal
	$t = 0x483 if c::is_ext3($dev);
    }
    $t;
}

#-######################################################################################
#- Functions
#-######################################################################################
sub empty_all_hds() {
    { hds => [], lvms => [], raids => [], loopbacks => [], raw_hds => [], nfss => [], smbs => [], davs => [], special => [] };
}
sub recompute_loopbacks {
    my ($all_hds) = @_;
    my @fstab = get_all_fstab($all_hds);
    @{$all_hds->{loopbacks}} = map { isPartOfLoopback($_) ? @{$_->{loopback}} : () } @fstab;
}

sub raids {
    my ($hds) = @_;

    my @parts = get_fstab(@$hds);
    {
	my @l = grep { isRawRAID($_) } @parts or return [];
	detect_devices::raidAutoStart(@l);
    }

    fs::get_major_minor(@parts);

    my @raids;
    my @mdstat = cat_("/proc/mdstat");
    for (my $i = 0; $i < @mdstat; $i++) {

	my ($nb, $level, $mdparts) = 
	  #- line format is:
	  #- md%d : {in}?active{ (read-only)}? {linear|raid1|raid4|raid5}{ DEVNAME[%d]{(F)}?}*
	  $mdstat[$i] =~ /^md(\d+).* ([^ \[\]]+) (\S+\[\d+\].*)/ or next;

	$level =~ s/raid//; #- { linear | raid0 | raid1 | raid5 } -> { linear | 0 | 1 | 5 }

	my $chunks = $mdstat[$i+1] =~ /(\S+) chunks/ ? $1 : "64k";

	my @raw_mdparts = map { /([^\[]+)/ } split ' ', $mdparts;

	my $type = typeOfPart("md$nb");
	log::l("RAID: found md$nb (raid $level) chunks $chunks ", if_($type, "type $type "), "with parts ", join(", ", @raw_mdparts));
	$raids[$nb] = { 'chunk-size' => $chunks, type => $type || 0x83, raw_mdparts => \@raw_mdparts,
			device => "md$nb", notFormatted => !$type, level => $level };
    }

    my %devname2part = map { $_->{dev} => { %$_, device => $_->{dev} } } devices::read_proc_partitions_raw();
    each_index {
	my $raw_mdparts = delete $_->{raw_mdparts};
	my @mdparts = 
	  map { 
	      my $mdpart = $devname2part{$_} || { device => $_ };
	      if (my $part = find { is_same_hd($mdpart, $_) } @parts, @raids) {
		  $part->{raid} = $::i;
		  $part->{type} = 0xfd;
		  delete $part->{mntpoint};
		  $part;
	      } else {
		  #- forget it when not found? that way it won't break much... beurk.
		  ();
	      }
	  } @$raw_mdparts;

	$_->{disks} = \@mdparts;
    } @raids;

    require raid;
    raid::update(@raids);
    \@raids;
}

sub lvms {
    my ($all_hds) = @_;
    my @pvs = grep { isRawLVM($_) } get_all_fstab($all_hds) or return;

    #- otherwise vgscan won't find them
    devices::make($_->{device}) foreach @pvs; 
    require lvm;

    my @lvms;
    foreach (@pvs) {
	my $name = lvm::get_vg($_) or next;
	my $lvm = find { $_->{VG_name} eq $name } @lvms;
	if (!$lvm) {
	    $lvm = new lvm($name);
	    lvm::update_size($lvm);
	    lvm::get_lvs($lvm);
	    push @lvms, $lvm;
	}
	$_->{lvm} = $name;
	push @{$lvm->{disks}}, $_;
    }
    @lvms;
}

sub hds {
    my ($flags, $o_ask_before_blanking) = @_;
    $flags ||= {};
    $flags->{readonly} && ($flags->{clearall} || $flags->{clear}) and die "conflicting flags readonly and clear/clearall";

    my @drives = detect_devices::hds();

    my (@hds, @raw_hds);
    foreach my $hd (@drives) {
	$hd->{file} = devices::make($hd->{device});
	$hd->{prefix} ||= $hd->{device};
	$hd->{readonly} = $flags->{readonly};

	my $h = partition_table::raw::get_geometry($hd->{file}) or log::l("An error occurred while getting the geometry of block device $hd->{file}: $!"), next;
	add2hash_($hd, $h);

	eval { partition_table::raw::test_for_bad_drives($hd) };
	if (my $err = $@) {
	    if ($err =~ /write error:/) { 
		$hd->{readonly} = 1;
	    } else {
		cdie $err if $err !~ /read error:/;
		next;
	    }
	}

	if ($flags->{clearall} || member($hd->{device}, @{$flags->{clear} || []})) {
	    partition_table::raw::zero_MBR_and_dirty($hd);
	} else {
	    eval { 
		partition_table::read($hd); 
		compare_with_proc_partitions($hd) if $::isInstall;
	    };
	    if (my $err = $@) {
		if ($hd->{readonly}) {
		    log::l("using /proc/partitions since diskdrake failed :(");
		    use_proc_partitions($hd);
		} elsif (exists $hd->{usb_description} && ($hd->{type} ||= typeOfPart($hd->{device}))) {
		    push @raw_hds, $hd;
		    next;
		} elsif ($o_ask_before_blanking && $o_ask_before_blanking->($hd->{device}, $err)) {
		    partition_table::raw::zero_MBR($hd);
		} else {
		    #- using it readonly
		    log::l("using /proc/partitions since diskdrake failed :(");
		    use_proc_partitions($hd);
		}
	    }
	    member($_->{device}, @{$flags->{clear} || []}) and partition_table::remove($hd, $_)
	      foreach partition_table::get_normal_parts($hd);
	}

	# special case for Various type
	$_->{type} = typeOfPart($_->{device}) || 0x100 foreach grep { $_->{type} == 0x100 } partition_table::get_normal_parts($hd);

	#- special case for type overloading (eg: reiserfs is 0x183)
	foreach (grep { isExt2($_) || $_->{type} == 0x7 } partition_table::get_normal_parts($hd)) {
	    my $type = typeOfPart($_->{device});
	    $_->{type} = $type if ($type & 0xff) == $_->{type} || $type && $hd->isa('partition_table::gpt');
	}
	push @hds, $hd;
    }

    #- detect raids before LVM allowing LVM on raid
    my $raids = raids(\@hds);
    my $all_hds = { %{ empty_all_hds() }, hds => \@hds, raw_hds => \@raw_hds, lvms => [], raids => $raids };

    $all_hds->{lvms} = [ lvms($all_hds) ];

    fs::get_major_minor(get_all_fstab($all_hds));

    $all_hds;
}

sub get_hds {
    #- $in is optional
    my ($flags, $o_in) = @_;

    if ($o_in) {
	catch_cdie { hds($flags, sub {
	    my ($dev, $err) = @_;
            $o_in->ask_yesorno(N("Error"), 
N("I can't read the partition table of device %s, it's too corrupted for me :(
I can try to go on, erasing over bad partitions (ALL DATA will be lost!).
The other solution is to not allow DrakX to modify the partition table.
(the error is %s)

Do you agree to lose all the partitions?
", $dev, formatError($err)));
        }) } sub { $o_in->ask_okcancel('', formatError($@)) };
    } else {
	catch_cdie { hds($flags) } sub { 1 }
    }
}

sub read_proc_partitions {
    my ($hds) = @_;

    my @all = devices::read_proc_partitions_raw();
    my @parts = grep { $_->{dev} =~ /\d$/ } @all;
    my @disks = grep { $_->{dev} !~ /\d$/ } @all;

    my $devfs_like = any { $_->{dev} =~ m|/disc$| } @disks;

    my %devfs2normal = map {
	my (undef, $major, $minor) = devices::entry($_->{device});
	my $disk = find { $_->{major} == $major && $_->{minor} == $minor } @disks;
	$disk->{dev} => $_->{device};
    } @$hds;

    my $prev_part;
    foreach my $part (@parts) {
	my $dev;
	if ($devfs_like) {
	    $dev = -e "/dev/$part->{dev}" ? $part->{dev} : sprintf("0x%x%02x", $part->{major}, $part->{minor});
	    $part->{rootDevice} = $devfs2normal{dirname($part->{dev}) . '/disc'};
	} else {
	    $dev = $part->{dev};
	    foreach my $hd (@$hds) {
		$part->{rootDevice} = $hd->{device} if $part->{dev} =~ /^$hd->{device}./;
	    }
	}
	undef $prev_part if $prev_part && ($prev_part->{rootDevice} || '') ne ($part->{rootDevice} || '');

	$part->{device} = $dev;
	$part->{size} *= 2;	# from KB to sectors
	$part->{type} = typeOfPart($dev); 
	$part->{start} = $prev_part ? $prev_part->{start} + $prev_part->{size} : 0;
	$prev_part = $part;
	delete $part->{dev}; # cleanup
    }
    @parts;
}

sub all_hds {
    my ($all_hds) = @_;
    (@{$all_hds->{hds}}, @{$all_hds->{lvms}});
}
sub part2hd {
    my ($part, $all_hds) = @_;
    my $hd = find { $part->{rootDevice} eq ($_->{device} || $_->{VG_name}) } all_hds($all_hds);
    $hd;
}

sub is_same_hd {
    my ($hd1, $hd2) = @_;
    if ($hd1->{major} && $hd2->{major}) {
	$hd1->{major} == $hd2->{major} && $hd1->{minor} == $hd2->{minor};
    } elsif (my ($s1) = $hd1->{device} =~ m|https?://(.+?)/*$|) {
	my ($s2) = $hd2->{device} =~ m|https?://(.+?)/*$|;
	$s1 eq $s2;
    } else {
	$hd1->{device} eq $hd2->{device};
    }
}

sub is_same_part {
    my ($part1, $part2) = @_;
    foreach ('start', 'size', 'type', 'rootDevice') {
	$part1->{$_} eq $part2->{$_} or return;
    }
    1;
}

#- get all normal partition including special ones as found on sparc.
sub get_fstab {
    map { partition_table::get_normal_parts($_) } @_;
}

#- get normal partition that should be visible for working on.
sub get_visible_fstab {
    grep { $_ && !partition_table::isWholedisk($_) && !partition_table::isHiddenMacPart($_) }
      map { partition_table::get_normal_parts($_) } @_;
}

sub get_fstab_and_holes {
    map {
	if (isLVM($_)) {
	    my @parts = partition_table::get_normal_parts($_);
	    my $free = $_->{totalsectors} - sum map { $_->{size} } @parts;
	    my $free_part = { start => 0, size => $free, type => 0, rootDevice => $_->{VG_name} };
	    @parts, if_($free >= $_->cylinder_size, $free_part);
	} else {
	    partition_table::get_normal_parts_and_holes($_);
	}
    } @_;
}
sub get_holes {
    grep { $_->{type} == 0 } get_fstab_and_holes(@_);
}

sub get_all_fstab {
    my ($all_hds) = @_;
    my @parts = map { partition_table::get_normal_parts($_) } all_hds($all_hds);
    my @raids = grep { $_ } @{$all_hds->{raids}};
    @parts, @raids, @{$all_hds->{loopbacks}};
}
sub get_really_all_fstab {
    my ($all_hds) = @_;
    my @parts = map { partition_table::get_normal_parts($_) } all_hds($all_hds);
    my @raids = grep { $_ } @{$all_hds->{raids}};
    @parts, @raids, @{$all_hds->{loopbacks}}, @{$all_hds->{raw_hds}}, @{$all_hds->{nfss}}, @{$all_hds->{smbs}}, @{$all_hds->{davs}};
}
sub get_all_fstab_and_holes {
    my ($all_hds) = @_;
    my @raids = grep { $_ } @{$all_hds->{raids}};
    get_fstab_and_holes(all_hds($all_hds)), @raids, @{$all_hds->{loopbacks}};
}
sub get_all_holes {
    my ($all_hds) = @_;
    grep { $_->{type} == 0 } get_all_fstab_and_holes($all_hds);
}

sub all_free_space {
    my ($all_hds) = @_;
    sum map { $_->{size} } get_all_holes($all_hds);
}
sub free_space {
    sum map { $_->{size} } get_holes(@_);
}

sub is_one_big_fat_or_NT {
    my ($hds) = @_;
    @$hds == 1 or return;

    my @l = get_fstab(@$hds);
    @l == 1 && isFat_or_NTFS($l[0]) && free_space(@$hds) < 10 << 11;
}

sub file2part {
    my ($fstab, $file, $b_keep_simple_symlinks) = @_;    
    my $part;

    $file = $b_keep_simple_symlinks ? common::expand_symlinks_but_simple("$::prefix$file") : expand_symlinks("$::prefix$file");
    unless ($file =~ s/^$::prefix//) {
	my $part = find { loopback::carryRootLoopback($_) } @$fstab or die;
	log::l("found $part->{mntpoint}");
	$file =~ s|/initrd/loopfs|$part->{mntpoint}|;
    }
    foreach (@$fstab) {
	my $m = $_->{mntpoint};
	$part = $_ if 
	  $file =~ /^\Q$m/ && 
	    (!$part || length $part->{mntpoint} < length $m);
    }
    $part or die "file2part: not found $file";
    $file =~ s|$part->{mntpoint}/?|/|;
    ($part, $file);
}


sub computeSize {
    my ($part, $best, $all_hds, $suggestions) = @_;
    my $max = $part->{maxsize} || $part->{size};
    return min($max, $best->{size}) unless $best->{ratio};

    my $free_space = all_free_space($all_hds);
    my @l = my @L = grep { 
	if ($free_space >= $_->{size}) {
	    $free_space -= $_->{size};
	    1;
	} else { 0 } } @$suggestions;

    my $cylinder_size_maxsize_adjusted;
    my $tot_ratios = 0;
    while (1) {
	my $old_free_space = $free_space;
	my $old_tot_ratios = $tot_ratios;

	$tot_ratios = sum(map { $_->{ratio} } @l);
	last if $tot_ratios == $old_tot_ratios;

	@l = grep { 
	    if ($_->{ratio} && $_->{maxsize} && $tot_ratios &&
		$_->{size} + $_->{ratio} / $tot_ratios * $old_free_space >= $_->{maxsize}) {
		return min($max, $best->{maxsize}) if $best->{mntpoint} eq $_->{mntpoint};
		$free_space -= $_->{maxsize} - $_->{size};
		if (!$cylinder_size_maxsize_adjusted++) {
		    eval { $free_space += part2hd($part, $all_hds)->cylinder_size - 1 };
		}
		0;
	    } else {
		$_->{ratio};
	    } 
	} @l;
    }
    my $size = int min($max, $best->{size} + $free_space * ($tot_ratios && $best->{ratio} / $tot_ratios));
    #- verify other entry can fill the hole
    (any { $_->{size} < $max - $size } @L) ? $size : $max;
}

sub suggest_part {
    my ($part, $all_hds, $o_suggestions) = @_;
    my $suggestions = $o_suggestions || $suggestions{server} || $suggestions{simple};

    my $has_swap = any { isSwap($_) } get_all_fstab($all_hds);

    my @local_suggestions =
      grep { !has_mntpoint($_->{mntpoint}, $all_hds) || isSwap($_) && !$has_swap }
      grep { !$_->{hd} || $_->{hd} eq $part->{rootDevice} }
	@$suggestions;

    my ($best) =
      grep { !$_->{maxsize} || $part->{size} <= $_->{maxsize} }
      grep { $_->{size} <= ($part->{maxsize} || $part->{size}) }
      grep { !$part->{type} || $part->{type} == $_->{type} || isTrueFS($part) && isTrueFS($_) }
	@local_suggestions;

    defined $best or return; #- sorry no suggestion :(

    $part->{mntpoint} = $best->{mntpoint};
    $part->{type} = $best->{type} if !(isTrueFS($best) && isTrueFS($part));
    $part->{size} = computeSize($part, $best, $all_hds, \@local_suggestions);
    foreach ('options', 'lv_name', 'encrypt_key') {
	$part->{$_} = $best->{$_} if $best->{$_};
    }
    1;
}

sub suggestions_mntpoint {
    my ($all_hds) = @_;
    sort grep { !/swap/ && !has_mntpoint($_, $all_hds) }
      (@suggestions_mntpoints, map { $_->{mntpoint} } @{$suggestions{server} || $suggestions{simple}});
}

sub mntpoint2part {
    my ($mntpoint, $fstab) = @_;
    find { $mntpoint eq $_->{mntpoint} } @$fstab;
}
sub has_mntpoint {
    my ($mntpoint, $all_hds) = @_;
    mntpoint2part($mntpoint, [ get_really_all_fstab($all_hds) ]);
}
sub get_root_ {
    my ($fstab, $o_boot) = @_;
    $o_boot && mntpoint2part("/boot", $fstab) || mntpoint2part("/", $fstab);
}
sub get_root { &get_root_ || {} }

#- do this before modifying $part->{type}
sub check_type {
    my ($type, $_hd, $part) = @_;
    isThisFs("jfs", { type => $type }) && $part->{size} < 16 << 11 and die \N("You can't use JFS for partitions smaller than 16MB");
    isThisFs("reiserfs", { type => $type }) && $part->{size} < 32 << 11 and die \N("You can't use ReiserFS for partitions smaller than 32MB");
}

sub package_needed_for_partition_type {
    my ($part) = @_;
    my %l = (
	reiserfs => 'reiserfsprogs',
	xfs => 'xfsprogs',
        jfs => 'jfsprogs',
    );
    $l{type2fs($part)};
}

#- you can do this before modifying $part->{mntpoint}
#- so $part->{mntpoint} should not be used here, use $mntpoint instead
sub check_mntpoint {
    my ($mntpoint, $hd, $part, $all_hds) = @_;

    $mntpoint eq '' || isSwap($part) || isNonMountable($part) and return;
    $mntpoint =~ m|^/| or die \N("Mount points must begin with a leading /");
    $mntpoint =~ m|[\x7f-\xff]| and cdie \N("Mount points should contain only alphanumerical characters");
    mntpoint2part($mntpoint, [ grep { $_ ne $part } get_really_all_fstab($all_hds) ]) and die \N("There is already a partition with mount point %s\n", $mntpoint);

    cdie \N("You've selected a software RAID partition as root (/).
No bootloader is able to handle this without a /boot partition.
Please be sure to add a /boot partition") if $mntpoint eq "/" && isRAID($part) && !has_mntpoint("/boot", $all_hds);
    die \N("You can't use a LVM Logical Volume for mount point %s", $mntpoint)
      if $mntpoint eq '/boot' && isLVM($hd);
    cdie \N("You may not be able to install lilo (since lilo doesn't handle a LV on multiple PVs)")
      if arch() =~ /i.86/ && member($mntpoint, '/', '/boot') && isLVM($hd) && @{$hd->{disks} || []} > 1;

    cdie \N("This directory should remain within the root filesystem")
      if member($mntpoint, qw(/root));
    die \N("This directory should remain within the root filesystem")
      if member($mntpoint, qw(/bin /dev /etc /lib /sbin /mnt));
    die \N("You need a true filesystem (ext2/ext3, reiserfs, xfs, or jfs) for this mount point\n")
      if !isTrueFS($part) && member($mntpoint, qw(/ /home /tmp /usr /var));
    die \N("You can't use an encrypted file system for mount point %s", $mntpoint)
      if $part->{options} =~ /encrypted/ && member($mntpoint, qw(/ /usr /var /boot));

    local $part->{mntpoint} = $mntpoint;
    loopback::check_circular_mounts($hd, $part, $all_hds);
}

sub add {
    my ($hd, $part, $all_hds, $options) = @_;

    isSwap($part) ?
      ($part->{mntpoint} = 'swap') :
      $options->{force} || check_mntpoint($part->{mntpoint}, $hd, $part, $all_hds);

    delete $part->{maxsize};

    if (isLVM($hd)) {
	lvm::lv_create($hd, $part);