propellor-5.3.0: property-based host configuration management in haskell

Safe HaskellNone
LanguageHaskell98

Propellor.Property.DiskImage.PartSpec

Contents

Description

Disk image partition specification.

Synopsis

Documentation

type PartSpec t = (Maybe MountPoint, MountOpts, PartSize -> Partition, t) Source #

Specifies a mount point, mount options, and a constructor for a Partition that determines its size.

data Fs Source #

Filesystems etc that can be used for a partition.

Constructors

EXT2 
EXT3 
EXT4 
BTRFS 
REISERFS 
XFS 
FAT 
VFAT 
NTFS 
LinuxSwap 

Instances

Eq Fs Source # 

Methods

(==) :: Fs -> Fs -> Bool #

(/=) :: Fs -> Fs -> Bool #

Show Fs Source # 

Methods

showsPrec :: Int -> Fs -> ShowS #

show :: Fs -> String #

showList :: [Fs] -> ShowS #

PartedVal Fs Source # 

Methods

pval :: Fs -> String Source #

partition :: Monoid t => Fs -> PartSpec t Source #

Specifies a partition with a given filesystem.

The partition is not mounted anywhere by default; use the combinators below to configure it.

PartSpec combinators

swapPartition :: Monoid t => PartSize -> PartSpec t Source #

Specifies a swap partition of a given size.

rawPartition :: Monoid t => PartSize -> PartSpec t Source #

Specifies a partition without any filesystem, of a given size.

mountedAt :: PartSpec t -> MountPoint -> PartSpec t Source #

Specifies where to mount a partition.

addFreeSpace :: PartSpec t -> PartSize -> PartSpec t Source #

Partitions in disk images default to being sized large enough to hold the files that live in that partition.

This adds additional free space to a partition.

setSize :: PartSpec t -> PartSize -> PartSpec t Source #

Specify a fixed size for a partition.

mountOpt :: ToMountOpts o => PartSpec t -> o -> PartSpec t Source #

Specifies a mount option, such as "noexec"

errorReadonly :: MountOpts Source #

Mount option to make a partition be remounted readonly when there's an error accessing it.

reservedSpacePercentage :: PartSpec t -> Int -> PartSpec t Source #

Sets the percent of the filesystem blocks reserved for the super-user.

The default is 5% for ext2 and ext4. Some filesystems may not support this.

setFlag :: PartSpec t -> PartFlag -> PartSpec t Source #

Sets a flag on the partition.

extended :: PartSpec t -> PartSpec t Source #

Makes a MSDOS partition be Extended, rather than Primary.

Partition properties

These properties do not do any disk partitioning on their own, but the Info they set can be used when building a disk image for a host.

hasPartition :: PartSpec PartLocation -> Property (HasInfo + UnixLike) Source #

Indicates that a host has a partition.

For example:

	& hasPartiton (partition EXT2 `mountedAt` "/boot" `partLocation` Beginning)
	& hasPartiton (partition EXT4 `mountedAt` "/")
	& hasPartiton (partition EXT4 `mountedAt` "/home" `partLocation` End `reservedSpacePercentage` 0)

adjustPartition :: MountPoint -> (PartSpec PartLocation -> PartSpec PartLocation) -> Property (HasInfo + UnixLike) Source #

Adjusts the PartSpec for the partition mounted at the specified location.

For example:

	& adjustPartition "/boot" (`addFreeSpace` MegaBytes 150)

hasPartitionTableType :: TableType -> Property (HasInfo + UnixLike) Source #

Indicates the partition table type of a host.

When not specified, the default is MSDOS.

For example:

	& hasPartitionTableType GPT

data TableType Source #

Types of partition tables supported by parted.

Constructors

MSDOS 
GPT 
AIX 
AMIGA 
BSD 
DVH 
LOOP 
MAC 
PC98 
SUN 

data PartTableSpec Source #

Specifies a partition table.

Constructors

PartTableSpec TableType [PartSpec ()]