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

Safe HaskellNone
LanguageHaskell98

Propellor.Property.Installer.Target

Contents

Description

Installation to a target disk.

Note that the RevertableProperties in this module are not really revertable; the target disk can't be put back how it was. The RevertableProperty type is used only to let them be used in a Versioned Host as shown below.

Here's an example of a noninteractive installer image using these properties.

There are two versions of Hosts, the installer and the target system.

data Variety = Installer | Target
	deriving (Eq)

The seed of both the installer and the target. They have some properties in common, and some different properties. The targetInstalled property knows how to convert the installer it's running on into a target system.

seed :: Versioned Variety Host
seed ver = host "debian.local" $ props
	& osDebian Unstable X86_64
	& Hostname.sane
	& Apt.stdSourcesList
	& Apt.installed ["linux-image-amd64"]
	& Grub.installed PC
	& "en_US.UTF-8" `Locale.selectedFor` ["LANG"]
	& ver ( (== Installer) --> targetInstalled seed Target (userInput ver) parts)
	& ver ( (== Target)    --> fstabLists (userInput ver) parts)
	& ver ( (== Installer) --> targetBootable (userInput ver))
  where
	parts = TargetPartTable MSDOS
		[ partition EXT4 `mountedAt` "/"
			`useDiskSpace` RemainingSpace
		, swapPartition (MegaBytes 1024)
		]

The installer disk image can then be built from the seed as follows:

 installerBuilt :: RevertableProperty (HasInfo + DebianLike) Linux
 installerBuilt = imageBuilt (VirtualBoxPointer "/srv/installer.vmdk")
	(hostChroot (seed `version` installer) (Debootstrapped mempty))
	MSDOS
 	 [ partition EXT4 `mountedAt` "/"
		`setFlag` BootFlag
		`reservedSpacePercentage` 0
 		`addFreeSpace` MegaBytes 256
 	]

When the installer is booted up, and propellor is run, it installs to the target disk. Since this example is a noninteractive installer, the details of what it installs to are configured before it's built.

data HardCodedUserInput = HardCodedUserInput (Maybe TargetDiskDevice) (Maybe DiskEraseConfirmed)

instance UserInput HardCodedUserInput where 
	targetDiskDevice (HardCodedUserInput t _) = Just t
	diskEraseConfirmed (HardCodedUserInput _ c) = Just c

userInput :: Version -> HardCodedUserInput
userInput Installer =  HardCodedUserInput Nothing Nothing
userInput Target = HardCodedUserInput (Just (TargetDiskDevice "/dev/sda")) (Just DiskEraseConfirmed)

For an example of how to use this to make an interactive installer, see https://git.joeyh.name/index.cgi/secret-project.git/

Synopsis

Main interface

data TargetPartTable Source #

Partition table for the target disk.

targetInstalled :: UserInput i => Versioned v Host -> v -> i -> TargetPartTable -> RevertableProperty (HasInfo + DebianLike) (HasInfo + DebianLike) Source #

Property that installs the target system to the TargetDiskDevice specified in the UserInput. That device will be re-partitioned and formatted and all files erased.

The installation is done efficiently by rsyncing the installer's files to the target, which forms the basis for a chroot that is provisioned with the specified version of the Host. Thanks to Propellor.Property.Versioned, any unwanted properties of the installer will be automatically reverted in the chroot.

When there is no TargetDiskDevice or the user has not confirmed the installation, nothing is done except for installing dependencies. So, this can also be used as a property of the installer image.

fstabLists :: UserInput i => i -> TargetPartTable -> RevertableProperty Linux Linux Source #

Property for use in the target Host to set up its fstab. Should be passed the same TargetPartTable as targetInstalled.

Additional properties

mountTarget :: UserInput i => i -> [PartSpec DiskPart] -> RevertableProperty Linux Linux Source #

Gets the target mounted.

targetBootable :: UserInput i => i -> RevertableProperty Linux Linux Source #

Make the target bootable using whatever bootloader is installed on it.

Utility functions

targetDir :: FilePath Source #

Where the target disk is mounted while it's being installed.

probeDisk :: IO TargetDiskDevice Source #

This can be used to find a likely disk device to use as the target for an installation.

This is a bit of a hack; of course the user could be prompted but to avoid prompting, some heuristics... * It should not already be mounted. * Prefer disks big enough to comfortably hold a Linux installation, so at least 8 gb. (But, if the system only has a smaller disk, it should be used.) * A medium size internal disk is better than a large removable disk, because removable or added drives are often used for data storage on systems with smaller internal disk for the OS. (But, if the internal disk is too small, prefer removable disk; some systems have an unusably small internal disk.) * Prefer the first disk in BIOS order, all other things being equal, because the main OS disk typically comes first. This can be approximated by preferring devsda to devsdb.

findDiskDevices :: IO [FilePath] Source #

Find disk devices, such as devsda (not partitions)

Installation progress tracking

data TargetFilled Source #

How much of the target disks are used, compared with the size of the installer's root device. Since the main part of an installation is targetInstalled rsyncing the latter to the former, this allows roughly estimating the percent done while an install is running, and can be used in some sort of progress display.

checkTargetFilled :: TargetFilledHandle -> IO TargetFilled Source #

Get the current TargetFilled value. This is fast enough to be run multiple times per second without using much CPU.