summaryrefslogtreecommitdiff
path: root/src/Propellor
diff options
context:
space:
mode:
Diffstat (limited to 'src/Propellor')
-rw-r--r--src/Propellor/Bootstrap.hs4
-rw-r--r--src/Propellor/CmdLine.hs2
-rw-r--r--src/Propellor/Property/Bootstrap.hs2
-rw-r--r--src/Propellor/Property/ConfFile.hs14
-rw-r--r--src/Propellor/Property/DiskImage.hs99
-rw-r--r--src/Propellor/Property/DiskImage/PartSpec.hs88
-rw-r--r--src/Propellor/Property/Grub.hs44
-rw-r--r--src/Propellor/Property/LightDM.hs14
-rw-r--r--src/Propellor/Property/Network.hs70
-rw-r--r--src/Propellor/Property/OS.hs2
-rw-r--r--src/Propellor/Property/Parted.hs198
-rw-r--r--src/Propellor/Property/Parted/Types.hs119
-rw-r--r--src/Propellor/Property/Reboot.hs17
-rw-r--r--src/Propellor/Property/Rsync.hs5
-rw-r--r--src/Propellor/Property/SiteSpecific/JoeySites.hs80
-rw-r--r--src/Propellor/Property/Sudo.hs24
-rw-r--r--src/Propellor/Property/Systemd.hs64
-rw-r--r--src/Propellor/Property/Timezone.hs21
-rw-r--r--src/Propellor/Property/Versioned.hs124
-rw-r--r--src/Propellor/Types.hs4
-rw-r--r--src/Propellor/Types/Bootloader.hs2
-rw-r--r--src/Propellor/Types/Info.hs3
-rw-r--r--src/Propellor/Types/PartSpec.hs66
23 files changed, 752 insertions, 314 deletions
diff --git a/src/Propellor/Bootstrap.hs b/src/Propellor/Bootstrap.hs
index 21f051c9..21d29bcc 100644
--- a/src/Propellor/Bootstrap.hs
+++ b/src/Propellor/Bootstrap.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+
module Propellor.Bootstrap (
Bootstrapper(..),
Builder(..),
@@ -34,7 +36,7 @@ data Bootstrapper = Robustly Builder | OSOnly
deriving (Show)
data Builder = Cabal | Stack
- deriving (Show)
+ deriving (Show, Typeable)
defaultBootstrapper :: Bootstrapper
defaultBootstrapper = Robustly Cabal
diff --git a/src/Propellor/CmdLine.hs b/src/Propellor/CmdLine.hs
index a36ec7f5..cba5991d 100644
--- a/src/Propellor/CmdLine.hs
+++ b/src/Propellor/CmdLine.hs
@@ -204,7 +204,7 @@ updateFirst h canrebuild cmdline next = ifM hasOrigin
, next
)
--- If changes can be fetched from origin, Builds propellor (when allowed)
+-- If changes can be fetched from origin, builds propellor (when allowed)
-- and re-execs the updated propellor binary to continue.
-- Otherwise, runs the IO action to continue.
updateFirst' :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
diff --git a/src/Propellor/Property/Bootstrap.hs b/src/Propellor/Property/Bootstrap.hs
index 91d1a82f..f0759dae 100644
--- a/src/Propellor/Property/Bootstrap.hs
+++ b/src/Propellor/Property/Bootstrap.hs
@@ -30,7 +30,7 @@ import qualified Data.ByteString as B
bootstrapWith :: Bootstrapper -> Property (HasInfo + UnixLike)
bootstrapWith b = pureInfoProperty desc (InfoVal b)
where
- desc = "bootstrapped with " ++ case b of
+ desc = "propellor bootstrapped with " ++ case b of
Robustly Stack -> "stack"
Robustly Cabal -> "cabal"
OSOnly -> "OS packages only"
diff --git a/src/Propellor/Property/ConfFile.hs b/src/Propellor/Property/ConfFile.hs
index ce092ec9..76d52bd9 100644
--- a/src/Propellor/Property/ConfFile.hs
+++ b/src/Propellor/Property/ConfFile.hs
@@ -9,6 +9,7 @@ module Propellor.Property.ConfFile (
IniSection,
IniKey,
containsIniSetting,
+ lacksIniSetting,
hasIniSection,
lacksIniSection,
iniFileContains,
@@ -93,6 +94,19 @@ containsIniSetting f (header, key, value) = adjustIniSection
go (l:ls) = if isKeyVal l then confline : ls else l : go ls
isKeyVal x = (filter (/= ' ') . takeWhile (/= '=')) x `elem` [key, '#':key]
+-- | Removes a key=value setting from a section of an .ini file.
+-- Note that the section heading is left in the file, so this is not a
+-- perfect reversion of containsIniSetting.
+lacksIniSetting :: FilePath -> (IniSection, IniKey, String) -> Property UnixLike
+lacksIniSetting f (header, key, value) = adjustIniSection
+ (f ++ " section [" ++ header ++ "] lacks " ++ key ++ "=" ++ value)
+ header
+ (filter (/= confline))
+ id
+ f
+ where
+ confline = key ++ "=" ++ value
+
-- | Ensures that a .ini file exists and contains a section
-- with a given key=value list of settings.
hasIniSection :: FilePath -> IniSection -> [(IniKey, String)] -> Property UnixLike
diff --git a/src/Propellor/Property/DiskImage.hs b/src/Propellor/Property/DiskImage.hs
index 9300b201..f64f685a 100644
--- a/src/Propellor/Property/DiskImage.hs
+++ b/src/Propellor/Property/DiskImage.hs
@@ -13,6 +13,7 @@ module Propellor.Property.DiskImage (
imageRebuilt,
imageBuiltFrom,
imageExists,
+ vmdkBuiltFor,
Grub.BIOS(..),
) where
@@ -20,12 +21,12 @@ import Propellor.Base
import Propellor.Property.DiskImage.PartSpec
import Propellor.Property.Chroot (Chroot)
import Propellor.Property.Chroot.Util (removeChroot)
+import Propellor.Property.Mount
import qualified Propellor.Property.Chroot as Chroot
import qualified Propellor.Property.Grub as Grub
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
import Propellor.Property.Parted
-import Propellor.Property.Mount
import Propellor.Property.Fstab (SwapPartition(..), genFstab)
import Propellor.Property.Partition
import Propellor.Property.Rsync
@@ -33,8 +34,9 @@ import Propellor.Types.Info
import Propellor.Types.Bootloader
import Propellor.Container
import Utility.Path
+import Utility.FileMode
-import Data.List (isPrefixOf, isInfixOf, sortBy)
+import Data.List (isPrefixOf, isInfixOf, sortBy, unzip4)
import Data.Function (on)
import qualified Data.Map.Strict as M
import qualified Data.ByteString.Lazy as L
@@ -109,16 +111,16 @@ type DiskImage = FilePath
-- > & Apt.installed ["linux-image-amd64"]
-- > & Grub.installed PC
-- > & hasPassword (User "root")
-imageBuilt :: DiskImage -> (FilePath -> Chroot) -> TableType -> [PartSpec] -> RevertableProperty (HasInfo + DebianLike) Linux
+imageBuilt :: DiskImage -> (FilePath -> Chroot) -> TableType -> [PartSpec ()] -> RevertableProperty (HasInfo + DebianLike) Linux
imageBuilt = imageBuilt' False
-- | Like 'built', but the chroot is deleted and rebuilt from scratch each
-- time. This is more expensive, but useful to ensure reproducible results
-- when the properties of the chroot have been changed.
-imageRebuilt :: DiskImage -> (FilePath -> Chroot) -> TableType -> [PartSpec] -> RevertableProperty (HasInfo + DebianLike) Linux
+imageRebuilt :: DiskImage -> (FilePath -> Chroot) -> TableType -> [PartSpec ()] -> RevertableProperty (HasInfo + DebianLike) Linux
imageRebuilt = imageBuilt' True
-imageBuilt' :: Bool -> DiskImage -> (FilePath -> Chroot) -> TableType -> [PartSpec] -> RevertableProperty (HasInfo + DebianLike) Linux
+imageBuilt' :: Bool -> DiskImage -> (FilePath -> Chroot) -> TableType -> [PartSpec ()] -> RevertableProperty (HasInfo + DebianLike) Linux
imageBuilt' rebuild img mkchroot tabletype partspec =
imageBuiltFrom img chrootdir tabletype final partspec
`requires` Chroot.provisioned chroot
@@ -159,13 +161,13 @@ cachesCleaned = "cache cleaned" ==> (Apt.cacheCleaned `pickOS` skipit)
skipit = doNothing :: Property UnixLike
-- | Builds a disk image from the contents of a chroot.
-imageBuiltFrom :: DiskImage -> FilePath -> TableType -> Finalization -> [PartSpec] -> RevertableProperty (HasInfo + DebianLike) UnixLike
+imageBuiltFrom :: DiskImage -> FilePath -> TableType -> Finalization -> [PartSpec ()] -> RevertableProperty (HasInfo + DebianLike) UnixLike
imageBuiltFrom img chrootdir tabletype final partspec = mkimg <!> rmimg
where
desc = img ++ " built from " ++ chrootdir
mkimg = property' desc $ \w -> do
- -- unmount helper filesystems such as proc from the chroot
- -- before getting sizes
+ -- Unmount helper filesystems such as proc from the chroot
+ -- first; don't want to include the contents of those.
liftIO $ unmountBelow chrootdir
szm <- M.mapKeys (toSysDir chrootdir) . M.map toPartSize
<$> liftIO (dirSizes chrootdir)
@@ -174,16 +176,15 @@ imageBuiltFrom img chrootdir tabletype final partspec = mkimg <!> rmimg
let (mnts, mntopts, parttable) = fitChrootSize tabletype partspec $
map (calcsz mnts) mnts
ensureProperty w $
- imageExists img (partTableSize parttable)
- `before`
- partitioned YesReallyDeleteDiskContents img parttable
+ imageExists' img parttable
`before`
kpartx img (mkimg' mnts mntopts parttable)
mkimg' mnts mntopts parttable devs =
partitionsPopulated chrootdir mnts mntopts devs
`before`
imageFinalized final mnts mntopts devs parttable
- rmimg = File.notPresent img
+ rmimg = undoRevertableProperty (imageExists' img dummyparttable)
+ dummyparttable = PartTable tabletype []
partitionsPopulated :: FilePath -> [Maybe MountPoint] -> [MountOpts] -> [LoopDev] -> Property DebianLike
partitionsPopulated chrootdir mnts mntopts devs = property' desc $ \w ->
@@ -214,10 +215,10 @@ partitionsPopulated chrootdir mnts mntopts devs = property' desc $ \w ->
-- The constructor for each Partition is passed the size of the files
-- from the chroot that will be put in that partition.
-fitChrootSize :: TableType -> [PartSpec] -> [PartSize] -> ([Maybe MountPoint], [MountOpts], PartTable)
+fitChrootSize :: TableType -> [PartSpec ()] -> [PartSize] -> ([Maybe MountPoint], [MountOpts], PartTable)
fitChrootSize tt l basesizes = (mounts, mountopts, parttable)
where
- (mounts, mountopts, sizers) = unzip3 l
+ (mounts, mountopts, sizers, _) = unzip4 l
parttable = PartTable tt (zipWith id sizers basesizes)
-- | Generates a map of the sizes of the contents of
@@ -273,6 +274,29 @@ imageExists img isz = property ("disk image exists" ++ img) $ liftIO $ do
-- Common sector sizes are 512 and 4096; use 4096 as it's larger.
sectorsize = 4096 :: Double
+-- | Ensure that disk image file exists and is partitioned.
+--
+-- Avoids repartitioning the disk image, when a file of the right size
+-- already exists, and it has the same PartTable.
+imageExists' :: FilePath -> PartTable -> RevertableProperty DebianLike UnixLike
+imageExists' img parttable = (setup <!> cleanup) `describe` desc
+ where
+ desc = "disk image exists " ++ img
+ parttablefile = img ++ ".parttable"
+ setup = property' desc $ \w -> do
+ oldparttable <- liftIO $ catchDefaultIO "" $ readFileStrict parttablefile
+ res <- ensureProperty w $ imageExists img (partTableSize parttable)
+ if res == NoChange && oldparttable == show parttable
+ then return NoChange
+ else if res == FailedChange
+ then return FailedChange
+ else do
+ liftIO $ writeFile parttablefile (show parttable)
+ ensureProperty w $ partitioned YesReallyDeleteDiskContents img parttable
+ cleanup = File.notPresent img
+ `before`
+ File.notPresent parttablefile
+
-- | A property that is run after the disk image is created, with
-- its populated partition tree mounted in the provided
-- location from the provided loop devices. This is typically used to
@@ -339,35 +363,9 @@ unbootable msg = \_ _ -> property desc $ do
-- This does not install the grub package. You will need to add
-- the `Grub.installed` property to the chroot.
grubBooted :: Finalization
-grubBooted mnt loopdevs = combineProperties "disk image boots using grub" $ props
- -- bind mount host /dev so grub can access the loop devices
- & bindMount "/dev" (inmnt "/dev")
- & mounted "proc" "proc" (inmnt "/proc") mempty
- & mounted "sysfs" "sys" (inmnt "/sys") mempty
- -- update the initramfs so it gets the uuid of the root partition
- & inchroot "update-initramfs" ["-u"]
- `assume` MadeChange
- -- work around for http://bugs.debian.org/802717
- & check haveosprober (inchroot "chmod" ["-x", osprober])
- & inchroot "update-grub" []
- `assume` MadeChange
- & check haveosprober (inchroot "chmod" ["+x", osprober])
- & inchroot "grub-install" [wholediskloopdev]
- `assume` MadeChange
- -- sync all buffered changes out to the disk image
- -- may not be necessary, but seemed needed sometimes
- -- when using the disk image right away.
- & cmdProperty "sync" []
- `assume` NoChange
+grubBooted mnt loopdevs = Grub.bootsMounted mnt wholediskloopdev
+ `describe` "disk image boots using grub"
where
- -- cannot use </> since the filepath is absolute
- inmnt f = mnt ++ f
-
- inchroot cmd ps = cmdProperty "chroot" ([mnt, cmd] ++ ps)
-
- haveosprober = doesFileExist (inmnt osprober)
- osprober = "/etc/grub.d/30_os-prober"
-
-- It doesn't matter which loopdev we use; all
-- come from the same disk image, and it's the loop dev
-- for the whole disk image we seek.
@@ -387,3 +385,20 @@ toSysDir :: FilePath -> FilePath -> FilePath
toSysDir chrootdir d = case makeRelative chrootdir d of
"." -> "/"
sysdir -> "/" ++ sysdir
+
+-- | Builds a VirtualBox .vmdk file for the specified disk image file.
+vmdkBuiltFor :: FilePath -> RevertableProperty DebianLike UnixLike
+vmdkBuiltFor diskimage = (setup <!> cleanup)
+ `describe` (vmdkfile ++ " built")
+ where
+ vmdkfile = diskimage ++ ".vmdk"
+ setup = cmdProperty "VBoxManage"
+ [ "internalcommands", "createrawvmdk"
+ , "-filename", vmdkfile
+ , "-rawdisk", diskimage
+ ]
+ `changesFile` vmdkfile
+ `onChange` File.mode vmdkfile (combineModes (ownerWriteMode : readModes))
+ `requires` Apt.installed ["virtualbox"]
+ `requires` File.notPresent vmdkfile
+ cleanup = File.notPresent vmdkfile
diff --git a/src/Propellor/Property/DiskImage/PartSpec.hs b/src/Propellor/Property/DiskImage/PartSpec.hs
index 2b14baa0..55249889 100644
--- a/src/Propellor/Property/DiskImage/PartSpec.hs
+++ b/src/Propellor/Property/DiskImage/PartSpec.hs
@@ -1,32 +1,28 @@
-- | Disk image partition specification and combinators.
+-- Partitions in disk images default to being sized large enough to hold
+-- the files that appear in the directory where the partition is to be
+-- mounted. Plus a fudge factor, since filesystems have some space
+-- overhead.
+
module Propellor.Property.DiskImage.PartSpec (
+ module Propellor.Types.PartSpec,
module Propellor.Property.DiskImage.PartSpec,
- Partition,
- PartSize(..),
- PartFlag(..),
- TableType(..),
- Fs(..),
- MountPoint,
+ module Propellor.Property.Parted.Types,
+ module Propellor.Property.Partition,
) where
import Propellor.Base
import Propellor.Property.Parted
-import Propellor.Property.Mount
-
--- | Specifies a mount point, mount options, and a constructor for a Partition.
---
--- The size that is eventually provided is the amount of space needed to
--- hold the files that appear in the directory where the partition is to be
--- mounted. Plus a fudge factor, since filesystems have some space
--- overhead.
-type PartSpec = (Maybe MountPoint, MountOpts, PartSize -> Partition)
+import Propellor.Types.PartSpec
+import Propellor.Property.Parted.Types
+import Propellor.Property.Partition (Fs(..))
--- | Partitions that are not to be mounted (ie, LinuxSwap), or that have
--- no corresponding directory in the chroot will have 128 MegaBytes
--- provided as a default size.
-defSz :: PartSize
-defSz = MegaBytes 128
+-- | Adds additional free space to the partition.
+addFreeSpace :: PartSpec t -> PartSize -> PartSpec t
+addFreeSpace (mp, o, p, t) freesz = (mp, o, p', t)
+ where
+ p' = \sz -> p (sz <> freesz)
-- | Add 2% for filesystem overhead. Rationalle for picking 2%:
-- A filesystem with 1% overhead might just sneak by as acceptable.
@@ -35,55 +31,3 @@ defSz = MegaBytes 128
-- Add an additional 200 mb for temp files, journals, etc.
fudge :: PartSize -> PartSize
fudge (MegaBytes n) = MegaBytes (n + n `div` 100 * 2 + 3 + 200)
-
--- | Specifies a swap partition of a given size.
-swapPartition :: PartSize -> PartSpec
-swapPartition sz = (Nothing, mempty, const (mkPartition LinuxSwap sz))
-
--- | Specifies a partition with a given filesystem.
---
--- The partition is not mounted anywhere by default; use the combinators
--- below to configure it.
-partition :: Fs -> PartSpec
-partition fs = (Nothing, mempty, mkPartition fs)
-
--- | Specifies where to mount a partition.
-mountedAt :: PartSpec -> FilePath -> PartSpec
-mountedAt (_, o, p) mp = (Just mp, o, p)
-
--- | Specifies a mount option, such as "noexec"
-mountOpt :: ToMountOpts o => PartSpec -> o -> PartSpec
-mountOpt (mp, o, p) o' = (mp, o <> toMountOpts o', p)
-
--- | Mount option to make a partition be remounted readonly when there's an
--- error accessing it.
-errorReadonly :: MountOpts
-errorReadonly = toMountOpts "errors=remount-ro"
-
--- | Adds additional free space to the partition.
-addFreeSpace :: PartSpec -> PartSize -> PartSpec
-addFreeSpace (mp, o, p) freesz = (mp, o, \sz -> p (sz <> freesz))
-
--- | Forced a partition to be a specific size, instead of scaling to the
--- size needed for the files in the chroot.
-setSize :: PartSpec -> PartSize -> PartSpec
-setSize (mp, o, p) sz = (mp, o, const (p sz))
-
--- | 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.
-reservedSpacePercentage :: PartSpec -> Int -> PartSpec
-reservedSpacePercentage s percent = adjustp s $ \p ->
- p { partMkFsOpts = ("-m"):show percent:partMkFsOpts p }
-
--- | Sets a flag on the partition.
-setFlag :: PartSpec -> PartFlag -> PartSpec
-setFlag s f = adjustp s $ \p -> p { partFlags = (f, True):partFlags p }
-
--- | Makes a MSDOS partition be Extended, rather than Primary.
-extended :: PartSpec -> PartSpec
-extended s = adjustp s $ \p -> p { partType = Extended }
-
-adjustp :: PartSpec -> (Partition -> Partition) -> PartSpec
-adjustp (mp, o, p) f = (mp, o, f . p)
diff --git a/src/Propellor/Property/Grub.hs b/src/Propellor/Property/Grub.hs
index 4bad7b2b..739a63e9 100644
--- a/src/Propellor/Property/Grub.hs
+++ b/src/Propellor/Property/Grub.hs
@@ -3,6 +3,7 @@ module Propellor.Property.Grub where
import Propellor.Base
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
+import Propellor.Property.Mount
import Propellor.Property.Chroot (inChroot)
import Propellor.Types.Info
import Propellor.Types.Bootloader
@@ -89,3 +90,46 @@ chainPVGrub rootdev bootdev timeout = combineProperties desc $ props
xenshim = scriptProperty ["grub-mkimage --prefix '(" ++ bootdev ++ ")/boot/grub' -c /boot/load.cf -O x86_64-xen /usr/lib/grub/x86_64-xen/*.mod > /boot/xen-shim"]
`assume` MadeChange
`describe` "/boot-xen-shim"
+
+-- | This is a version of `boots` that makes grub boot the system mounted
+-- at a particular directory. The OSDevice should be the underlying disk
+-- device that grub will be installed to (generally a whole disk,
+-- not a partition).
+bootsMounted :: FilePath -> OSDevice -> Property Linux
+bootsMounted mnt wholediskdev = combineProperties desc $ props
+ -- bind mount host /dev so grub can access the loop devices
+ & bindMount "/dev" (inmnt "/dev")
+ & mounted "proc" "proc" (inmnt "/proc") mempty
+ & mounted "sysfs" "sys" (inmnt "/sys") mempty
+ -- update the initramfs so it gets the uuid of the root partition
+ & inchroot "update-initramfs" ["-u"]
+ `assume` MadeChange
+ -- work around for http://bugs.debian.org/802717
+ & check haveosprober (inchroot "chmod" ["-x", osprober])
+ & inchroot "update-grub" []
+ `assume` MadeChange
+ & check haveosprober (inchroot "chmod" ["+x", osprober])
+ & inchroot "grub-install" [wholediskdev]
+ `assume` MadeChange
+ & cleanupmounts
+ -- sync all buffered changes out to the disk in case it's
+ -- used right away
+ & cmdProperty "sync" []
+ `assume` NoChange
+ where
+ desc = "grub boots " ++ wholediskdev
+
+ -- cannot use </> since the filepath is absolute
+ inmnt f = mnt ++ f
+
+ inchroot cmd ps = cmdProperty "chroot" ([mnt, cmd] ++ ps)
+
+ haveosprober = doesFileExist (inmnt osprober)
+ osprober = "/etc/grub.d/30_os-prober"
+
+ cleanupmounts :: Property Linux
+ cleanupmounts = property desc $ liftIO $ do
+ umountLazy (inmnt "/sys")
+ umountLazy (inmnt "/proc")
+ umountLazy (inmnt "/dev")
+ return NoChange
diff --git a/src/Propellor/Property/LightDM.hs b/src/Propellor/Property/LightDM.hs
index 69538d89..d471d314 100644
--- a/src/Propellor/Property/LightDM.hs
+++ b/src/Propellor/Property/LightDM.hs
@@ -10,8 +10,12 @@ installed :: Property DebianLike
installed = Apt.installed ["lightdm"]
-- | Configures LightDM to skip the login screen and autologin as a user.
-autoLogin :: User -> Property DebianLike
-autoLogin (User u) = "/etc/lightdm/lightdm.conf" `ConfFile.containsIniSetting`
- ("SeatDefaults", "autologin-user", u)
- `describe` "lightdm autologin"
- `requires` installed
+autoLogin :: User -> RevertableProperty DebianLike DebianLike
+autoLogin (User u) = (setup <!> cleanup)
+ `describe` ("lightdm autologin for " ++ u)
+ where
+ cf = "/etc/lightdm/lightdm.conf"
+ setting = ("Seat:*", "autologin-user", u)
+ setup = cf `ConfFile.containsIniSetting` setting
+ `requires` installed
+ cleanup = tightenTargets $ cf `ConfFile.lacksIniSetting` setting
diff --git a/src/Propellor/Property/Network.hs b/src/Propellor/Property/Network.hs
index 9ed9e591..b581fa3f 100644
--- a/src/Propellor/Property/Network.hs
+++ b/src/Propellor/Property/Network.hs
@@ -7,6 +7,9 @@ import Data.Char
type Interface = String
+-- | Options to put in a stanza of an ifupdown interfaces file.
+type InterfaceOptions = [(String, String)]
+
ifUp :: Interface -> Property DebianLike
ifUp iface = tightenTargets $ cmdProperty "ifup" [iface]
`assume` MadeChange
@@ -19,27 +22,57 @@ ifUp iface = tightenTargets $ cmdProperty "ifup" [iface]
--
-- No interfaces are brought up or down by this property.
cleanInterfacesFile :: Property DebianLike
-cleanInterfacesFile = tightenTargets $ hasContent interfacesFile
- [ "# Deployed by propellor, do not edit."
- , ""
- , "source-directory interfaces.d"
+cleanInterfacesFile = interfaceFileContains interfacesFile
+ [ "source-directory interfaces.d"
, ""
, "# The loopback network interface"
, "auto lo"
, "iface lo inet loopback"
]
+ []
`describe` ("clean " ++ interfacesFile)
-- | Configures an interface to get its address via dhcp.
dhcp :: Interface -> Property DebianLike
-dhcp iface = tightenTargets $ hasContent (interfaceDFile iface)
+dhcp iface = dhcp' iface mempty
+
+dhcp' :: Interface -> InterfaceOptions -> Property DebianLike
+dhcp' iface options = interfaceFileContains (interfaceDFile iface)
[ "auto " ++ iface
, "iface " ++ iface ++ " inet dhcp"
- ]
+ ] options
`describe` ("dhcp " ++ iface)
`requires` interfacesDEnabled
--- | Writes a static interface file for the specified interface.
+newtype Gateway = Gateway IPAddr
+
+-- | Configures an interface with a static address and gateway.
+static :: Interface -> IPAddr -> Maybe Gateway -> Property DebianLike
+static iface addr gateway = static' iface addr gateway mempty
+
+static' :: Interface -> IPAddr -> Maybe Gateway -> InterfaceOptions -> Property DebianLike
+static' iface addr gateway options =
+ interfaceFileContains (interfaceDFile iface) headerlines options'
+ `describe` ("static IP address for " ++ iface)
+ `requires` interfacesDEnabled
+ where
+ headerlines =
+ [ "auto " ++ iface
+ , "iface " ++ iface ++ " " ++ inet ++ " static"
+ ]
+ options' = catMaybes
+ [ Just $ ("address", val addr)
+ , case gateway of
+ Just (Gateway gaddr) ->
+ Just ("gateway", val gaddr)
+ Nothing -> Nothing
+ ] ++ options
+ inet = case addr of
+ IPv4 _ -> "inet"
+ IPv6 _ -> "inet6"
+
+-- | Writes a static interface file for the specified interface
+-- to preserve its current configuration.
--
-- The interface has to be up already. It could have been brought up by
-- DHCP, or by other means. The current ipv4 addresses
@@ -50,8 +83,8 @@ dhcp iface = tightenTargets $ hasContent (interfaceDFile iface)
--
-- (ipv6 addresses are not included because it's assumed they come up
-- automatically in most situations.)
-static :: Interface -> Property DebianLike
-static iface = tightenTargets $
+preserveStatic :: Interface -> Property DebianLike
+preserveStatic iface = tightenTargets $
check (not <$> doesFileExist f) setup
`describe` desc
`requires` interfacesDEnabled
@@ -84,13 +117,13 @@ static iface = tightenTargets $
-- | 6to4 ipv6 connection, should work anywhere
ipv6to4 :: Property DebianLike
-ipv6to4 = tightenTargets $ hasContent (interfaceDFile "sit0")
- [ "# Deployed by propellor, do not edit."
+ipv6to4 = tightenTargets $ interfaceFileContains (interfaceDFile "sit0")
+ [ "auto sit0"
, "iface sit0 inet6 static"
- , "\taddress 2002:5044:5531::1"
- , "\tnetmask 64"
- , "\tgateway ::192.88.99.1"
- , "auto sit0"
+ ]
+ [ ("address", "2002:5044:5531::1")
+ , ("netmask", "64")
+ , ("gateway", "::192.88.99.1")
]
`describe` "ipv6to4"
`requires` interfacesDEnabled
@@ -114,3 +147,10 @@ interfacesDEnabled :: Property DebianLike
interfacesDEnabled = tightenTargets $
containsLine interfacesFile "source-directory interfaces.d"
`describe` "interfaces.d directory enabled"
+
+interfaceFileContains :: FilePath -> [String] -> InterfaceOptions -> Property DebianLike
+interfaceFileContains f headerlines options = tightenTargets $ hasContent f $
+ warning : headerlines ++ map fmt options
+ where
+ fmt (k, v) = "\t" ++ k ++ " " ++ v
+ warning = "# Deployed by propellor, do not edit."
diff --git a/src/Propellor/Property/OS.hs b/src/Propellor/Property/OS.hs
index 10d7afc0..c31bef7b 100644
--- a/src/Propellor/Property/OS.hs
+++ b/src/Propellor/Property/OS.hs
@@ -207,7 +207,7 @@ preserveNetwork = go `requires` Network.cleanInterfacesFile
["route", "list", "scope", "global"]
case words <$> headMaybe ls of
Just ("default":"via":_:"dev":iface:_) ->
- ensureProperty w $ Network.static iface
+ ensureProperty w $ Network.preserveStatic iface
_ -> do
warningMessage "did not find any default ipv4 route"
return FailedChange
diff --git a/src/Propellor/Property/Parted.hs b/src/Propellor/Property/Parted.hs
index f7ac379f..43744142 100644
--- a/src/Propellor/Property/Parted.hs
+++ b/src/Propellor/Property/Parted.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleContexts #-}
module Propellor.Property.Parted (
+ -- * Types
TableType(..),
PartTable(..),
partTableSize,
@@ -15,137 +16,30 @@ module Propellor.Property.Parted (
Partition.MkfsOpts,
PartType(..),
PartFlag(..),
- Eep(..),
+ -- * Properties
partitioned,
parted,
+ Eep(..),
installed,
+ -- * PartSpec combinators
+ calcPartTable,
+ DiskSize(..),
+ DiskPart,
+ module Propellor.Types.PartSpec,
+ DiskSpaceUse(..),
+ useDiskSpace,
) where
import Propellor.Base
+import Propellor.Property.Parted.Types
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Pacman as Pacman
import qualified Propellor.Property.Partition as Partition
+import Propellor.Types.PartSpec
import Utility.DataUnits
-import Data.Char
-import System.Posix.Files
-
-class PartedVal a where
- pval :: a -> String
-
--- | Types of partition tables supported by parted.
-data TableType = MSDOS | GPT | AIX | AMIGA | BSD | DVH | LOOP | MAC | PC98 | SUN
- deriving (Show)
-
-instance PartedVal TableType where
- pval = map toLower . show
-
--- | A disk's partition table.
-data PartTable = PartTable TableType [Partition]
- deriving (Show)
-
-instance Monoid PartTable where
- -- | default TableType is MSDOS
- mempty = PartTable MSDOS []
- -- | uses the TableType of the second parameter
- mappend (PartTable _l1 ps1) (PartTable l2 ps2) = PartTable l2 (ps1 ++ ps2)
-
--- | Gets the total size of the disk specified by the partition table.
-partTableSize :: PartTable -> ByteSize
-partTableSize (PartTable _ ps) = fromPartSize $
- -- add 1 megabyte to hold the partition table itself
- mconcat (MegaBytes 1 : map partSize ps)
-
--- | A partition on the disk.
-data Partition = Partition
- { partType :: PartType
- , partSize :: PartSize
- , partFs :: Partition.Fs
- , partMkFsOpts :: Partition.MkfsOpts
- , partFlags :: [(PartFlag, Bool)] -- ^ flags can be set or unset (parted may set some flags by default)
- , partName :: Maybe String -- ^ optional name for partition (only works for GPT, PC98, MAC)
- }
- deriving (Show)
-
--- | Makes a Partition with defaults for non-important values.
-mkPartition :: Partition.Fs -> PartSize -> Partition
-mkPartition fs sz = Partition
- { partType = Primary
- , partSize = sz
- , partFs = fs
- , partMkFsOpts = []
- , partFlags = []
- , partName = Nothing
- }
-
--- | Type of a partition.
-data PartType = Primary | Logical | Extended
- deriving (Show)
-
-instance PartedVal PartType where
- pval Primary = "primary"
- pval Logical = "logical"
- pval Extended = "extended"
-
--- | All partition sizing is done in megabytes, so that parted can
--- automatically lay out the partitions.
---
--- Note that these are SI megabytes, not mebibytes.
-newtype PartSize = MegaBytes Integer
- deriving (Show)
-
-instance PartedVal PartSize where
- pval (MegaBytes n)
- | n > 0 = val n ++ "MB"
- -- parted can't make partitions smaller than 1MB;
- -- avoid failure in edge cases
- | otherwise = "1MB"
--- | Rounds up to the nearest MegaByte.
-toPartSize :: ByteSize -> PartSize
-toPartSize b = MegaBytes $ ceiling (fromInteger b / 1000000 :: Double)
-
-fromPartSize :: PartSize -> ByteSize
-fromPartSize (MegaBytes b) = b * 1000000
-
-instance Monoid PartSize where
- mempty = MegaBytes 0
- mappend (MegaBytes a) (MegaBytes b) = MegaBytes (a + b)
-
-reducePartSize :: PartSize -> PartSize -> PartSize
-reducePartSize (MegaBytes a) (MegaBytes b) = MegaBytes (a - b)
-
--- | Flags that can be set on a partition.
-data PartFlag = BootFlag | RootFlag | SwapFlag | HiddenFlag | RaidFlag | LvmFlag | LbaFlag | LegacyBootFlag | IrstFlag | EspFlag | PaloFlag
- deriving (Show)
-
-instance PartedVal PartFlag where
- pval BootFlag = "boot"
- pval RootFlag = "root"
- pval SwapFlag = "swap"
- pval HiddenFlag = "hidden"
- pval RaidFlag = "raid"
- pval LvmFlag = "lvm"
- pval LbaFlag = "lba"
- pval LegacyBootFlag = "legacy_boot"
- pval IrstFlag = "irst"
- pval EspFlag = "esp"
- pval PaloFlag = "palo"
-
-instance PartedVal Bool where
- pval True = "on"
- pval False = "off"
-
-instance PartedVal Partition.Fs where
- pval Partition.EXT2 = "ext2"
- pval Partition.EXT3 = "ext3"
- pval Partition.EXT4 = "ext4"
- pval Partition.BTRFS = "btrfs"
- pval Partition.REISERFS = "reiserfs"
- pval Partition.XFS = "xfs"
- pval Partition.FAT = "fat"
- pval Partition.VFAT = "vfat"
- pval Partition.NTFS = "ntfs"
- pval Partition.LinuxSwap = "linux-swap"
+import System.Posix.Files
+import Data.List (genericLength)
data Eep = YesReallyDeleteDiskContents
@@ -202,3 +96,67 @@ parted YesReallyDeleteDiskContents disk ps = p `requires` installed
-- | Gets parted installed.
installed :: Property (DebianLike + ArchLinux)
installed = Apt.installed ["parted"] `pickOS` Pacman.installed ["parted"]
+
+-- | Gets the total size of the disk specified by the partition table.
+partTableSize :: PartTable -> ByteSize
+partTableSize (PartTable _ ps) = fromPartSize $
+ mconcat (partitionTableOverhead : map partSize ps)
+
+-- | Some disk is used to store the partition table itself. Assume less
+-- than 1 mb.
+partitionTableOverhead :: PartSize
+partitionTableOverhead = MegaBytes 1
+
+-- | Calculate a partition table, for a given size of disk.
+--
+-- For example:
+--
+-- > calcPartTable (DiskSize (1024 * 1024 * 1024 * 100)) MSDOS
+-- > [ partition EXT2 `mountedAt` "/boot"
+-- > `setSize` MegaBytes 256
+-- > `setFlag` BootFlag
+-- > , partition EXT4 `mountedAt` "/"
+-- > `useDisk` RemainingSpace
+-- > ]
+calcPartTable :: DiskSize -> TableType -> [PartSpec DiskPart] -> PartTable
+calcPartTable (DiskSize disksize) tt l = PartTable tt (map go l)
+ where
+ go (_, _, mkpart, FixedDiskPart) = mkpart defSz
+ go (_, _, mkpart, DynamicDiskPart (Percent p)) = mkpart $ toPartSize $
+ diskremainingafterfixed * fromIntegral p `div` 100
+ go (_, _, mkpart, DynamicDiskPart RemainingSpace) = mkpart $ toPartSize $
+ diskremaining `div` genericLength (filter isremainingspace l)
+ diskremainingafterfixed =
+ disksize - sumsizes (filter isfixed l)
+ diskremaining =
+ disksize - sumsizes (filter (not . isremainingspace) l)
+ sumsizes = sum . map fromPartSize . (partitionTableOverhead :) .
+ map (partSize . go)
+ isfixed (_, _, _, FixedDiskPart) = True
+ isfixed _ = False
+ isremainingspace (_, _, _, DynamicDiskPart RemainingSpace) = True
+ isremainingspace _ = False
+
+-- | Size of a disk, in bytes.
+newtype DiskSize = DiskSize ByteSize
+ deriving (Show)
+
+data DiskPart = FixedDiskPart | DynamicDiskPart DiskSpaceUse
+
+data DiskSpaceUse = Percent Int | RemainingSpace
+
+instance Monoid DiskPart
+ where
+ mempty = FixedDiskPart
+ mappend FixedDiskPart FixedDiskPart = FixedDiskPart
+ mappend (DynamicDiskPart (Percent a)) (DynamicDiskPart (Percent b)) = DynamicDiskPart (Percent (a + b))
+ mappend (DynamicDiskPart RemainingSpace) (DynamicDiskPart RemainingSpace) = DynamicDiskPart RemainingSpace
+ mappend (DynamicDiskPart (Percent a)) _ = DynamicDiskPart (Percent a)
+ mappend _ (DynamicDiskPart (Percent b)) = DynamicDiskPart (Percent b)
+ mappend (DynamicDiskPart RemainingSpace) _ = DynamicDiskPart RemainingSpace
+ mappend _ (DynamicDiskPart RemainingSpace) = DynamicDiskPart RemainingSpace
+
+-- | Make a partition use some percentage of the size of the disk
+-- (less all fixed size partitions), or the remaining space in the disk.
+useDiskSpace :: PartSpec DiskPart -> DiskSpaceUse -> PartSpec DiskPart
+useDiskSpace (mp, o, p, _) diskuse = (mp, o, p, DynamicDiskPart diskuse)
diff --git a/src/Propellor/Property/Parted/Types.hs b/src/Propellor/Property/Parted/Types.hs
new file mode 100644
index 00000000..3350e008
--- /dev/null
+++ b/src/Propellor/Property/Parted/Types.hs
@@ -0,0 +1,119 @@
+module Propellor.Property.Parted.Types where
+
+import Propellor.Base
+import qualified Propellor.Property.Partition as Partition
+import Utility.DataUnits
+
+import Data.Char
+
+class PartedVal a where
+ pval :: a -> String
+
+-- | Types of partition tables supported by parted.
+data TableType = MSDOS | GPT | AIX | AMIGA | BSD | DVH | LOOP | MAC | PC98 | SUN
+ deriving (Show)
+
+instance PartedVal TableType where
+ pval = map toLower . show
+
+-- | A disk's partition table.
+data PartTable = PartTable TableType [Partition]
+ deriving (Show)
+
+instance Monoid PartTable where
+ -- | default TableType is MSDOS
+ mempty = PartTable MSDOS []
+ -- | uses the TableType of the second parameter
+ mappend (PartTable _l1 ps1) (PartTable l2 ps2) = PartTable l2 (ps1 ++ ps2)
+
+-- | A partition on the disk.
+data Partition = Partition
+ { partType :: PartType
+ , partSize :: PartSize
+ , partFs :: Partition.Fs
+ , partMkFsOpts :: Partition.MkfsOpts
+ , partFlags :: [(PartFlag, Bool)] -- ^ flags can be set or unset (parted may set some flags by default)
+ , partName :: Maybe String -- ^ optional name for partition (only works for GPT, PC98, MAC)
+ }
+ deriving (Show)
+
+-- | Makes a Partition with defaults for non-important values.
+mkPartition :: Partition.Fs -> PartSize -> Partition
+mkPartition fs sz = Partition
+ { partType = Primary
+ , partSize = sz
+ , partFs = fs
+ , partMkFsOpts = []
+ , partFlags = []
+ , partName = Nothing
+ }
+
+-- | Type of a partition.
+data PartType = Primary | Logical | Extended
+ deriving (Show)
+
+instance PartedVal PartType where
+ pval Primary = "primary"
+ pval Logical = "logical"
+ pval Extended = "extended"
+
+-- | All partition sizing is done in megabytes, so that parted can
+-- automatically lay out the partitions.
+--
+-- Note that these are SI megabytes, not mebibytes.
+newtype PartSize = MegaBytes Integer
+ deriving (Show)
+
+instance PartedVal PartSize where
+ pval (MegaBytes n)
+ | n > 0 = val n ++ "MB"
+ -- parted can't make partitions smaller than 1MB;
+ -- avoid failure in edge cases
+ | otherwise = "1MB"
+
+-- | Rounds up to the nearest MegaByte.
+toPartSize :: ByteSize -> PartSize
+toPartSize b = MegaBytes $ ceiling (fromInteger b / 1000000 :: Double)
+
+fromPartSize :: PartSize -> ByteSize
+fromPartSize (MegaBytes b) = b * 1000000
+
+instance Monoid PartSize where
+ mempty = MegaBytes 0
+ mappend (MegaBytes a) (MegaBytes b) = MegaBytes (a + b)
+
+reducePartSize :: PartSize -> PartSize -> PartSize
+reducePartSize (MegaBytes a) (MegaBytes b) = MegaBytes (a - b)
+
+-- | Flags that can be set on a partition.
+data PartFlag = BootFlag | RootFlag | SwapFlag | HiddenFlag | RaidFlag | LvmFlag | LbaFlag | LegacyBootFlag | IrstFlag | EspFlag | PaloFlag
+ deriving (Show)
+
+instance PartedVal PartFlag where
+ pval BootFlag = "boot"
+ pval RootFlag = "root"
+ pval SwapFlag = "swap"
+ pval HiddenFlag = "hidden"
+ pval RaidFlag = "raid"
+ pval LvmFlag = "lvm"
+ pval LbaFlag = "lba"
+ pval LegacyBootFlag = "legacy_boot"
+ pval IrstFlag = "irst"
+ pval EspFlag = "esp"
+ pval PaloFlag = "palo"
+
+instance PartedVal Bool where
+ pval True = "on"
+ pval False = "off"
+
+instance PartedVal Partition.Fs where
+ pval Partition.EXT2 = "ext2"
+ pval Partition.EXT3 = "ext3"
+ pval Partition.EXT4 = "ext4"
+ pval Partition.BTRFS = "btrfs"
+ pval Partition.REISERFS = "reiserfs"
+ pval Partition.XFS = "xfs"
+ pval Partition.FAT = "fat"
+ pval Partition.VFAT = "vfat"
+ pval Partition.NTFS = "ntfs"
+ pval Partition.LinuxSwap = "linux-swap"
diff --git a/src/Propellor/Property/Reboot.hs b/src/Propellor/Property/Reboot.hs
index 3781cd7b..909d87fb 100644
--- a/src/Propellor/Property/Reboot.hs
+++ b/src/Propellor/Property/Reboot.hs
@@ -78,15 +78,16 @@ toKernelNewerThan ver =
property' ("reboot to kernel newer than " ++ ver) $ \w -> do
wantV <- tryReadVersion ver
runningV <- tryReadVersion =<< liftIO runningKernelVersion
- installedV <- maximum <$>
- (mapM tryReadVersion =<< liftIO installedKernelVersions)
if runningV >= wantV then noChange
- else if installedV >= wantV
- then ensureProperty w now
- else errorMessage $
- "kernel newer than "
- ++ ver
- ++ " not installed"
+ else maximum <$> installedVs >>= \installedV ->
+ if installedV >= wantV
+ then ensureProperty w now
+ else errorMessage $
+ "kernel newer than "
+ ++ ver
+ ++ " not installed"
+ where
+ installedVs = mapM tryReadVersion =<< liftIO installedKernelVersions
runningInstalledKernel :: IO Bool
runningInstalledKernel = do
diff --git a/src/Propellor/Property/Rsync.hs b/src/Propellor/Property/Rsync.hs
index 53baa74e..5665ab91 100644
--- a/src/Propellor/Property/Rsync.hs
+++ b/src/Propellor/Property/Rsync.hs
@@ -60,4 +60,7 @@ syncDirFiltered filters src dest = rsync $
rsync :: [String] -> Property (DebianLike + ArchLinux)
rsync ps = cmdProperty "rsync" ps
`assume` MadeChange
- `requires` Apt.installed ["rsync"] `pickOS` Pacman.installed ["rsync"]
+ `requires` installed
+
+installed :: Property (DebianLike + ArchLinux)
+installed = Apt.installed ["rsync"] `pickOS` Pacman.installed ["rsync"]
diff --git a/src/Propellor/Property/SiteSpecific/JoeySites.hs b/src/Propellor/Property/SiteSpecific/JoeySites.hs
index 6e0d6c4e..d686f3d9 100644
--- a/src/Propellor/Property/SiteSpecific/JoeySites.hs
+++ b/src/Propellor/Property/SiteSpecific/JoeySites.hs
@@ -19,6 +19,7 @@ import qualified Propellor.Property.Obnam as Obnam
import qualified Propellor.Property.Apache as Apache
import qualified Propellor.Property.Postfix as Postfix
import qualified Propellor.Property.Systemd as Systemd
+import qualified Propellor.Property.Network as Network
import qualified Propellor.Property.Fail2Ban as Fail2Ban
import qualified Propellor.Property.LetsEncrypt as LetsEncrypt
import Utility.FileMode
@@ -929,3 +930,82 @@ alarmClock oncalendar (User user) command = combineProperties "goodmorning timer
& Systemd.started "goodmorning.timer"
& "/etc/systemd/logind.conf" `ConfFile.containsIniSetting`
("Login", "LidSwitchIgnoreInhibited", "no")
+
+-- My home router, running hostapd and dnsmasq for wlan0,
+-- with eth0 connected to a satellite modem, and a fallback ppp connection.
+homeRouter :: Property (HasInfo + DebianLike)
+homeRouter = propertyList "home router" $ props
+ & Network.static "wlan0" (IPv4 "10.1.1.1") Nothing
+ `requires` Network.cleanInterfacesFile
+ & Apt.serviceInstalledRunning "hostapd"
+ `requires` File.hasContent "/etc/hostapd/hostapd.conf"
+ [ "interface=wlan0"
+ , "ssid=house"
+ , "hw_mode=g"
+ , "channel=8"
+ ]
+ `requires` File.dirExists "/lib/hostapd"
+ & Apt.serviceInstalledRunning "dnsmasq"
+ `requires` File.hasContent "/etc/dnsmasq.conf"
+ [ "domain-needed"
+ , "bogus-priv"
+ , "interface=wlan0"
+ , "domain=kitenet.net"
+ , "dhcp-range=10.1.1.100,10.1.1.150,24h"
+ , "no-hosts"
+ , "address=/honeybee.kitenet.net/10.1.1.1"
+ ]
+ `requires` File.hasContent "/etc/resolv.conf"
+ [ "domain kitenet.net"
+ , "search kitenet.net"
+ , "nameserver 8.8.8.8"
+ , "nameserver 8.8.4.4"
+ ]
+ & ipmasq "wlan0"
+ & Apt.serviceInstalledRunning "netplug"
+ & Network.static' "eth0" (IPv4 "192.168.1.42")
+ (Just (Network.Gateway (IPv4 "192.168.1.1")))
+ -- When satellite is down, fall back to dialup
+ [ ("pre-up", "poff -a || true")
+ , ("post-down", "pon")
+ ]
+ `requires` Network.cleanInterfacesFile
+ & Apt.installed ["ppp"]
+ `before` File.hasContent "/etc/ppp/peers/provider"
+ [ "user \"joeyh@arczip.com\""
+ , "connect \"/usr/sbin/chat -v -f /etc/chatscripts/pap -T 9734111\""
+ , "/dev/ttyACM0"
+ , "115200"
+ , "noipdefault"
+ , "defaultroute"
+ , "persist"
+ , "noauth"
+ ]
+ `before` File.hasPrivContent "/etc/ppp/pap-secrets" (Context "joeyh@arczip.com")
+
+-- | Enable IP masqerading, on whatever other interfaces come up than the
+-- provided intif.
+ipmasq :: String -> Property DebianLike
+ipmasq intif = File.hasContent ifupscript
+ [ "#!/bin/sh"
+ , "INTIF=" ++ intif
+ , "if [ \"$IFACE\" = $INTIF ] || [ \"$IFACE\" = lo ]; then"
+ , "exit 0"
+ , "fi"
+ , "iptables -F"
+ , "iptables -A FORWARD -i $IFACE -o $INTIF -m state --state ESTABLISHED,RELATED -j ACCEPT"
+ , "iptables -A FORWARD -i $INTIF -o $IFACE -j ACCEPT"
+ , "iptables -t nat -A POSTROUTING -o $IFACE -j MASQUERADE"
+ , "echo 1 > /proc/sys/net/ipv4/ip_forward"
+ ]
+ `before` scriptmode ifupscript
+ `before` File.hasContent pppupscript
+ [ "#!/bin/sh"
+ , "IFACE=$PPP_IFACE " ++ ifupscript
+ ]
+ `before` scriptmode pppupscript
+ `requires` Apt.installed ["iptables"]
+ where
+ ifupscript = "/etc/network/if-up.d/ipmasq"
+ pppupscript = "/etc/ppp/ip-up.d/ipmasq"
+ scriptmode f = f `File.mode` combineModes (readModes ++ executeModes)
diff --git a/src/Propellor/Property/Sudo.hs b/src/Propellor/Property/Sudo.hs
index 45ab8af2..1614801d 100644
--- a/src/Propellor/Property/Sudo.hs
+++ b/src/Propellor/Property/Sudo.hs
@@ -9,23 +9,33 @@ import Propellor.Property.User
-- | Allows a user to sudo. If the user has a password, sudo is configured
-- to require it. If not, NOPASSWORD is enabled for the user.
-enabledFor :: User -> Property DebianLike
-enabledFor user@(User u) = go `requires` Apt.installed ["sudo"]
+enabledFor :: User -> RevertableProperty DebianLike DebianLike
+enabledFor user@(User u) = setup `requires` Apt.installed ["sudo"] <!> cleanup
where
- go :: Property UnixLike
- go = property' desc $ \w -> do
+ setup :: Property UnixLike
+ setup = property' desc $ \w -> do
locked <- liftIO $ isLockedPassword user
ensureProperty w $
fileProperty desc
(modify locked . filter (wanted locked))
- "/etc/sudoers"
- desc = u ++ " is sudoer"
+ sudoers
+ where
+ desc = u ++ " is sudoer"
+
+ cleanup :: Property DebianLike
+ cleanup = tightenTargets $
+ fileProperty desc (filter notuserline) sudoers
+ where
+ desc = u ++ " is not sudoer"
+
+ sudoers = "/etc/sudoers"
sudobaseline = u ++ " ALL=(ALL:ALL)"
+ notuserline l = not (sudobaseline `isPrefixOf` l)
sudoline True = sudobaseline ++ " NOPASSWD:ALL"
sudoline False = sudobaseline ++ " ALL"
wanted locked l
-- TOOD: Full sudoers file format parse..
- | not (sudobaseline `isPrefixOf` l) = True
+ | notuserline l = True
| "NOPASSWD" `isInfixOf` l = locked
| otherwise = True
modify locked ls
diff --git a/src/Propellor/Property/Systemd.hs b/src/Propellor/Property/Systemd.hs
index d1a94aa8..51d1313c 100644
--- a/src/Propellor/Property/Systemd.hs
+++ b/src/Propellor/Property/Systemd.hs
@@ -283,54 +283,42 @@ nspawned c@(Container name (Chroot.Chroot loc builder _ _) h) =
chroot = Chroot.Chroot loc builder Chroot.propagateChrootInfo h
--- | Sets up the service file for the container, and then starts
--- it running.
+-- | Sets up the service files for the container, using the
+-- systemd-nspawn@.service template, and starts it running.
nspawnService :: Container -> ChrootCfg -> RevertableProperty Linux Linux
nspawnService (Container name _ _) cfg = setup <!> teardown
where
service = nspawnServiceName name
- servicefile = "/etc/systemd/system/multi-user.target.wants" </> service
-
- servicefilecontent = do
- ls <- lines <$> readFile "/lib/systemd/system/systemd-nspawn@.service"
- return $ unlines $
- "# deployed by propellor" : map addparams ls
- addparams l
- | "ExecStart=" `isPrefixOf` l = unwords $
- [ "ExecStart = /usr/bin/systemd-nspawn"
- , "--quiet"
- , "--keep-unit"
- , "--boot"
- , "--directory=" ++ containerDir name
- , "--machine=%i"
- ] ++ nspawnServiceParams cfg
- | otherwise = l
-
- goodservicefile = (==)
- <$> servicefilecontent
- <*> catchDefaultIO "" (readFile servicefile)
-
- writeservicefile :: Property Linux
- writeservicefile = property servicefile $ makeChange $ do
- c <- servicefilecontent
- File.viaStableTmp (\t -> writeFile t c) servicefile
-
- setupservicefile :: Property Linux
- setupservicefile = check (not <$> goodservicefile) $
- -- if it's running, it has the wrong configuration,
- -- so stop it
- stopped service
- `requires` daemonReloaded
- `requires` writeservicefile
+ overridedir = "/etc/systemd/system" </> nspawnServiceName name ++ ".d"
+ overridefile = overridedir </> "local.conf"
+ overridecontent =
+ [ "[Service]"
+ , "# Reset ExecStart from the template"
+ , "ExecStart="
+ , "ExecStart=/usr/bin/systemd-nspawn " ++ unwords nspawnparams
+ ]
+ nspawnparams =
+ [ "--quiet"
+ , "--keep-unit"
+ , "--boot"
+ , "--directory=" ++ containerDir name
+ , "--machine=" ++ name
+ ] ++ nspawnServiceParams cfg
+
+ overrideconfigured = File.hasContent overridefile overridecontent
+ `onChange` daemonReloaded
+ `requires` File.dirExists overridedir
setup :: Property Linux
setup = started service
- `requires` setupservicefile
+ `requires` enabled service
+ `requires` overrideconfigured
`requires` machined
teardown :: Property Linux
- teardown = check (doesFileExist servicefile) $
- disabled service `requires` stopped service
+ teardown = stopped service
+ `before` disabled service
+ `before` File.notPresent overridefile
nspawnServiceParams :: ChrootCfg -> [String]
nspawnServiceParams NoChrootCfg = []
diff --git a/src/Propellor/Property/Timezone.hs b/src/Propellor/Property/Timezone.hs
new file mode 100644
index 00000000..96a5e59c
--- /dev/null
+++ b/src/Propellor/Property/Timezone.hs
@@ -0,0 +1,21 @@
+-- | Maintainer: Sean Whitton <spwhitton@spwhitton.name>
+
+module Propellor.Property.Timezone where
+
+import Propellor.Base
+import qualified Propellor.Property.Apt as Apt
+import qualified Propellor.Property.File as File
+
+-- | A timezone from /usr/share/zoneinfo
+type Timezone = String
+
+-- | Sets the system's timezone
+configured :: Timezone -> Property DebianLike
+configured zone = File.hasContent "/etc/timezone" [zone]
+ `onChange` update
+ `describe` (zone ++ " timezone configured")
+ where
+ update = Apt.reConfigure "tzdata" mempty
+ -- work around a bug in recent tzdata. See
+ -- https://bugs.launchpad.net/ubuntu/+source/tzdata/+bug/1554806/
+ `requires` File.notPresent "/etc/localtime"
diff --git a/src/Propellor/Property/Versioned.hs b/src/Propellor/Property/Versioned.hs
new file mode 100644
index 00000000..87673c64
--- /dev/null
+++ b/src/Propellor/Property/Versioned.hs
@@ -0,0 +1,124 @@
+{-# LANGUAGE RankNTypes, FlexibleContexts, TypeFamilies #-}
+
+-- | Versioned properties and hosts.
+--
+-- When importing and using this module, you will need to enable some
+-- language extensions:
+--
+-- > {-# LANGUAGE RankNTypes, FlexibleContexts, TypeFamilies #-}
+--
+-- This module takes advantage of `RevertableProperty` to let propellor
+-- switch cleanly between versions. The way it works is all revertable
+-- properties for other versions than the current version are first
+-- reverted, and then propellor ensures the property for the current
+-- version. This method should work for any combination of revertable
+-- properties.
+--
+-- For example:
+--
+-- > demo :: Versioned Int (RevertableProperty DebianLike DebianLike)
+-- > demo ver =
+-- > ver ( (== 1) --> Apache.modEnabled "foo"
+-- > `requires` Apache.modEnabled "foosupport"
+-- > <|> (== 2) --> Apache.modEnabled "bar"
+-- > <|> (> 2) --> Apache.modEnabled "baz"
+-- > )
+-- >
+-- > foo :: Host
+-- > foo = host "foo.example.com" $ props
+-- > & demo `version` (2 :: Int)
+--
+-- Similarly, a whole Host can be versioned. For example:
+--
+-- > bar :: Versioned Int Host
+-- > bar ver = host "bar.example.com" $ props
+-- > & osDebian Unstable X86_64
+-- > & ver ( (== 1) --> Apache.modEnabled "foo"
+-- > <|> (== 2) --> Apache.modEnabled "bar"
+-- > )
+-- > & ver ( (>= 2) --> Apt.unattendedUpgrades )
+--
+-- Note that some versioning of revertable properties may cause
+-- propellor to do a lot of unnecessary work each time it's run.
+-- Here's an example of such a problem:
+--
+-- > slow :: Versioned Int -> RevertableProperty DebianLike DebianLike
+-- > slow ver =
+-- > ver ( (== 1) --> (Apt.installed "foo" <!> Apt.removed "foo")
+-- > <|> (== 2) --> (Apt.installed "bar" <!> Apt.removed "bar")
+-- > )
+--
+-- Suppose that package bar depends on package foo. Then at version 2,
+-- propellor will remove package foo in order to revert version 1, only
+-- to re-install it since version 2 also needs it installed.
+
+module Propellor.Property.Versioned (Versioned, version, (-->), (<|>)) where
+
+import Propellor
+import Propellor.Types.Core
+
+import Data.List
+
+-- | Something that has multiple versions of type `v`.
+type Versioned v t = VersionedBy v -> t
+
+type VersionedBy v
+ = forall metatypes. Combines (RevertableProperty metatypes metatypes) (RevertableProperty metatypes metatypes)
+ => (CombinedType (RevertableProperty metatypes metatypes) (RevertableProperty metatypes metatypes) ~ RevertableProperty metatypes metatypes)
+ => (VerSpec v metatypes -> RevertableProperty metatypes metatypes)
+
+-- | Access a particular version of a Versioned value.
+version :: (Versioned v t) -> v -> t
+version f v = f (processVerSpec v)
+
+-- A specification of versions.
+--
+-- Why is this not a simple list like
+-- [(v -> Bool, RevertableProperty metatypes metatypes)] ?
+-- Using a list would mean the empty list would need to be dealt with,
+-- and processVerSpec does not have a Monoid instance for
+-- RevertableProperty metatypes metatypes in scope, and due to the way the
+-- Versioned type works, the compiler cannot find such an instance.
+--
+-- Also, using this data type allows a nice syntax for creating
+-- VerSpecs, via the `<&>` and `alt` functions.
+data VerSpec v metatypes
+ = Base (v -> Bool, RevertableProperty metatypes metatypes)
+ | More (v -> Bool, RevertableProperty metatypes metatypes) (VerSpec v metatypes)
+
+processVerSpec
+ :: Combines (RevertableProperty metatypes metatypes) (RevertableProperty metatypes metatypes)
+ => (CombinedType (RevertableProperty metatypes metatypes) (RevertableProperty metatypes metatypes) ~ RevertableProperty metatypes metatypes)
+ => v
+ -> VerSpec v metatypes
+ -> RevertableProperty metatypes metatypes
+processVerSpec v s = combinedp s
+ `describe` intercalate " and " (combineddesc s [])
+ where
+ combinedp (Base (c, p))
+ | c v = p
+ | otherwise = revert p
+ combinedp (More (c, p) vs)
+ | c v = combinedp vs `before` p
+ | otherwise = revert p `before` combinedp vs
+ combineddesc (Base (c, p)) l
+ | c v = getDesc p : l
+ | otherwise = getDesc (revert p) : l
+ combineddesc (More (c, p) vs) l
+ | c v = getDesc p : combineddesc vs l
+ | otherwise = getDesc (revert p) : combineddesc vs l
+
+-- | Specify a function that checks the version, and what
+-- `RevertableProperty` to use if the version matches.
+(-->) :: (v -> Bool) -> RevertableProperty metatypes metatypes -> VerSpec v metatypes
+c --> p = Base (c, p)
+
+-- | Add an alternate version.
+(<|>) :: VerSpec v metatypes -> VerSpec v metatypes -> VerSpec v metatypes
+Base a <|> Base b = More a (Base b)
+Base a <|> More b c = More a (More b c)
+More b c <|> Base a = More a (More b c)
+More a b <|> More c d = More a (More c (b <|> d))
+
+infixl 8 -->
+infixl 2 <|>
diff --git a/src/Propellor/Types.hs b/src/Propellor/Types.hs
index 155662c2..b7c7c7f7 100644
--- a/src/Propellor/Types.hs
+++ b/src/Propellor/Types.hs
@@ -107,6 +107,10 @@ adjustPropertySatisfy (Property t d s i c) f = Property t d (f <$> s) i c
-- | A property that can be reverted. The first Property is run
-- normally and the second is run when it's reverted.
+--
+-- See `Propellor.Property.Versioned.Versioned`
+-- for a way to use RevertableProperty to define different
+-- versions of a host.
data RevertableProperty setupmetatypes undometatypes = RevertableProperty
{ setupRevertableProperty :: Property setupmetatypes
, undoRevertableProperty :: Property undometatypes
diff --git a/src/Propellor/Types/Bootloader.hs b/src/Propellor/Types/Bootloader.hs
index c6953b94..4a75503a 100644
--- a/src/Propellor/Types/Bootloader.hs
+++ b/src/Propellor/Types/Bootloader.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FlexibleInstances, DeriveDataTypeable #-}
module Propellor.Types.Bootloader where
diff --git a/src/Propellor/Types/Info.hs b/src/Propellor/Types/Info.hs
index 06212780..6716c403 100644
--- a/src/Propellor/Types/Info.hs
+++ b/src/Propellor/Types/Info.hs
@@ -17,6 +17,7 @@ module Propellor.Types.Info (
import Data.Dynamic
import Data.Maybe
import Data.Monoid
+import qualified Data.Typeable as T
import Prelude
-- | Information about a Host, which can be provided by its properties.
@@ -35,7 +36,7 @@ instance Show InfoEntry where
-- Extracts the value from an InfoEntry but only when
-- it's of the requested type.
extractInfoEntry :: Typeable v => InfoEntry -> Maybe v
-extractInfoEntry (InfoEntry v) = cast v
+extractInfoEntry (InfoEntry v) = T.cast v
-- | Values stored in Info must be members of this class.
--
diff --git a/src/Propellor/Types/PartSpec.hs b/src/Propellor/Types/PartSpec.hs
new file mode 100644
index 00000000..2b0a8787
--- /dev/null
+++ b/src/Propellor/Types/PartSpec.hs
@@ -0,0 +1,66 @@
+-- | Partition specification combinators.
+
+module Propellor.Types.PartSpec where
+
+import Propellor.Base
+import Propellor.Property.Parted.Types
+import Propellor.Property.Mount
+import Propellor.Property.Partition
+
+-- | Specifies a mount point, mount options, and a constructor for a
+-- Partition that determines its size.
+type PartSpec t = (Maybe MountPoint, MountOpts, PartSize -> Partition, t)
+
+-- | Specifies a partition with a given filesystem.
+--
+-- The partition is not mounted anywhere by default; use the combinators
+-- below to configure it.
+partition :: Monoid t => Fs -> PartSpec t
+partition fs = (Nothing, mempty, mkPartition fs, mempty)
+
+-- | Specifies a swap partition of a given size.
+swapPartition :: Monoid t => PartSize -> PartSpec t
+swapPartition sz = (Nothing, mempty, const (mkPartition LinuxSwap sz), mempty)
+
+-- | Specifies where to mount a partition.
+mountedAt :: PartSpec t -> FilePath -> PartSpec t
+mountedAt (_, o, p, t) mp = (Just mp, o, p, t)
+
+-- | Specify a fixed size for a partition.
+setSize :: PartSpec t -> PartSize -> PartSpec t
+setSize (mp, o, p, t) sz = (mp, o, const (p sz), t)
+
+-- | Specifies a mount option, such as "noexec"
+mountOpt :: ToMountOpts o => PartSpec t -> o -> PartSpec t
+mountOpt (mp, o, p, t) o' = (mp, o <> toMountOpts o', p, t)
+
+-- | Mount option to make a partition be remounted readonly when there's an
+-- error accessing it.
+errorReadonly :: MountOpts
+errorReadonly = toMountOpts "errors=remount-ro"
+
+-- | 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.
+reservedSpacePercentage :: PartSpec t -> Int -> PartSpec t
+reservedSpacePercentage s percent = adjustp s $ \p ->
+ p { partMkFsOpts = ("-m"):show percent:partMkFsOpts p }
+
+-- | Sets a flag on the partition.
+setFlag :: PartSpec t -> PartFlag -> PartSpec t
+setFlag s f = adjustp s $ \p -> p { partFlags = (f, True):partFlags p }
+
+-- | Makes a MSDOS partition be Extended, rather than Primary.
+extended :: PartSpec t -> PartSpec t
+extended s = adjustp s $ \p -> p { partType = Extended }
+
+adjustp :: PartSpec t -> (Partition -> Partition) -> PartSpec t
+adjustp (mp, o, p, t) f = (mp, o, f . p, t)
+
+adjustt :: PartSpec t -> (t -> t) -> PartSpec t
+adjustt (mp, o, p, t) f = (mp, o, p, f t)
+
+-- | Default partition size when not otherwize specified is 128 MegaBytes.
+defSz :: PartSize
+defSz = MegaBytes 128