Safe Haskell | None |
---|---|
Language | Haskell2010 |
Propellor.Property.DiskImage.PartSpec
Description
Disk image partition specification.
Synopsis
- type PartSpec t = (Maybe MountPoint, MountOpts, PartSize -> Partition, t)
- data Fs
- data PartSize
- partition :: Monoid t => Fs -> PartSpec t
- swapPartition :: Monoid t => PartSize -> PartSpec t
- rawPartition :: Monoid t => PartSize -> PartSpec t
- mountedAt :: PartSpec t -> MountPoint -> PartSpec t
- addFreeSpace :: PartSpec t -> PartSize -> PartSpec t
- setSize :: PartSpec t -> PartSize -> PartSpec t
- mountOpt :: ToMountOpts o => PartSpec t -> o -> PartSpec t
- errorReadonly :: MountOpts
- reservedSpacePercentage :: PartSpec t -> Int -> PartSpec t
- setFlag :: PartSpec t -> PartFlag -> PartSpec t
- extended :: PartSpec t -> PartSpec t
- hasPartition :: PartSpec PartLocation -> Property (HasInfo + UnixLike)
- adjustPartition :: MountPoint -> (PartSpec PartLocation -> PartSpec PartLocation) -> Property (HasInfo + UnixLike)
- data PartLocation
- partLocation :: PartSpec PartLocation -> PartLocation -> PartSpec PartLocation
- hasPartitionTableType :: TableType -> Property (HasInfo + UnixLike)
- data TableType
- data PartInfo
- toPartTableSpec :: PartInfo -> PartTableSpec
- data PartTableSpec = PartTableSpec TableType [PartSpec ()]
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.
Filesystems etc that can be used for a partition.
Size of a partition.
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.
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.
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.
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)
data PartLocation Source #
Indicates partition layout in a disk. Default is somewhere in the middle.
Instances
Eq PartLocation Source # | |
Defined in Propellor.Property.DiskImage.PartSpec | |
Ord PartLocation Source # | |
Defined in Propellor.Property.DiskImage.PartSpec Methods compare :: PartLocation -> PartLocation -> Ordering # (<) :: PartLocation -> PartLocation -> Bool # (<=) :: PartLocation -> PartLocation -> Bool # (>) :: PartLocation -> PartLocation -> Bool # (>=) :: PartLocation -> PartLocation -> Bool # max :: PartLocation -> PartLocation -> PartLocation # min :: PartLocation -> PartLocation -> PartLocation # | |
Semigroup PartLocation Source # | |
Defined in Propellor.Property.DiskImage.PartSpec Methods (<>) :: PartLocation -> PartLocation -> PartLocation # sconcat :: NonEmpty PartLocation -> PartLocation # stimes :: Integral b => b -> PartLocation -> PartLocation # | |
Monoid PartLocation Source # | |
Defined in Propellor.Property.DiskImage.PartSpec Methods mempty :: PartLocation # mappend :: PartLocation -> PartLocation -> PartLocation # mconcat :: [PartLocation] -> PartLocation # |
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
Types of partition tables supported by parted.
Instances
data PartTableSpec Source #
Specifies a partition table.
Constructors
PartTableSpec TableType [PartSpec ()] |
Instances
Show PartTableSpec Source # | |
Defined in Propellor.Types.PartSpec Methods showsPrec :: Int -> PartTableSpec -> ShowS # show :: PartTableSpec -> String # showList :: [PartTableSpec] -> ShowS # |