Merge branch 'joeyconfig'

This commit is contained in:
Joey Hess 2014-11-21 17:29:47 -04:00
commit e60b261dae
9 changed files with 231 additions and 89 deletions

View File

@ -25,6 +25,7 @@ import qualified Propellor.Property.Grub as Grub
import qualified Propellor.Property.Obnam as Obnam import qualified Propellor.Property.Obnam as Obnam
import qualified Propellor.Property.Gpg as Gpg import qualified Propellor.Property.Gpg as Gpg
import qualified Propellor.Property.Chroot as Chroot import qualified Propellor.Property.Chroot as Chroot
import qualified Propellor.Property.Systemd as Systemd
import qualified Propellor.Property.HostingProvider.DigitalOcean as DigitalOcean import qualified Propellor.Property.HostingProvider.DigitalOcean as DigitalOcean
import qualified Propellor.Property.HostingProvider.CloudAtCost as CloudAtCost import qualified Propellor.Property.HostingProvider.CloudAtCost as CloudAtCost
import qualified Propellor.Property.HostingProvider.Linode as Linode import qualified Propellor.Property.HostingProvider.Linode as Linode
@ -80,10 +81,17 @@ clam = standardSystem "clam.kitenet.net" Unstable "amd64"
! Ssh.listenPort 80 ! Ssh.listenPort 80
! Ssh.listenPort 443 ! Ssh.listenPort 443
& Chroot.provisioned testChroot ! Chroot.provisioned testChroot
& Systemd.persistentJournal
& Systemd.nspawned meow
meow :: Systemd.Container
meow = Systemd.container "meow" (Chroot.debootstrapped (System (Debian Unstable) "amd64") mempty)
& Apt.serviceInstalledRunning "uptimed"
& alias "meow.kitenet.net"
testChroot :: Chroot.Chroot testChroot :: Chroot.Chroot
testChroot = Chroot.chroot "/tmp/chroot" (System (Debian Unstable) "amd64") testChroot = Chroot.debootstrapped (System (Debian Unstable) "amd64") mempty "/tmp/chroot"
& File.hasContent "/foo" ["hello"] & File.hasContent "/foo" ["hello"]
orca :: Host orca :: Host

1
debian/changelog vendored
View File

@ -13,7 +13,6 @@ propellor (1.0.0) UNRELEASED; urgency=medium
* DigitalOcean.distroKernel property now reboots into the distribution * DigitalOcean.distroKernel property now reboots into the distribution
kernel when necessary. kernel when necessary.
* Avoid outputting color setting sequences when not run on a terminal. * Avoid outputting color setting sequences when not run on a terminal.
* Run remote propellor --spin with a controlling terminal.
* Docker code simplified by using `docker exec`; needs docker 1.3.1. * Docker code simplified by using `docker exec`; needs docker 1.3.1.
* Docker containers are now a separate data type, cannot be included * Docker containers are now a separate data type, cannot be included
in the main host list, and are instead passed to in the main host list, and are instead passed to

View File

@ -96,6 +96,7 @@ Library
Propellor.Property.Ssh Propellor.Property.Ssh
Propellor.Property.Sudo Propellor.Property.Sudo
Propellor.Property.Systemd Propellor.Property.Systemd
Propellor.Property.Systemd.Core
Propellor.Property.Tor Propellor.Property.Tor
Propellor.Property.User Propellor.Property.User
Propellor.Property.HostingProvider.CloudAtCost Propellor.Property.HostingProvider.CloudAtCost

View File

@ -85,8 +85,8 @@ defaultMain hostlist = do
go _ (Edit field context) = editPrivData field context go _ (Edit field context) = editPrivData field context
go _ ListFields = listPrivDataFields hostlist go _ ListFields = listPrivDataFields hostlist
go _ (AddKey keyid) = addKey keyid go _ (AddKey keyid) = addKey keyid
go _ c@(ChrootChain _ _ _ _) = Chroot.chain hostlist c
go _ (DockerChain hn cid) = Docker.chain hostlist hn cid go _ (DockerChain hn cid) = Docker.chain hostlist hn cid
go _ (ChrootChain hn loc) = Chroot.chain hostlist hn loc
go _ (DockerInit hn) = Docker.init hn go _ (DockerInit hn) = Docker.init hn
go _ (GitPush fin fout) = gitPushHelper fin fout go _ (GitPush fin fout) = gitPushHelper fin fout
go _ (Update _) = forceConsole >> fetchFirst (onlyprocess update) go _ (Update _) = forceConsole >> fetchFirst (onlyprocess update)

View File

@ -1,12 +1,17 @@
module Propellor.Property.Chroot ( module Propellor.Property.Chroot (
Chroot(..), Chroot(..),
chroot, debootstrapped,
provisioned, provisioned,
-- * Internal use
provisioned',
propigateChrootInfo,
propellChroot,
chain, chain,
) where ) where
import Propellor import Propellor
import qualified Propellor.Property.Debootstrap as Debootstrap import qualified Propellor.Property.Debootstrap as Debootstrap
import qualified Propellor.Property.Systemd.Core as Systemd
import qualified Propellor.Shim as Shim import qualified Propellor.Shim as Shim
import Utility.SafeCommand import Utility.SafeCommand
@ -14,21 +19,33 @@ import qualified Data.Map as M
import Data.List.Utils import Data.List.Utils
import System.Posix.Directory import System.Posix.Directory
data Chroot = Chroot FilePath System Host data Chroot = Chroot FilePath System BuilderConf Host
deriving (Show)
data BuilderConf
= UsingDeboostrap Debootstrap.DebootstrapConfig
deriving (Show)
instance Hostlike Chroot where instance Hostlike Chroot where
(Chroot l s h) & p = Chroot l s (h & p) (Chroot l s c h) & p = Chroot l s c (h & p)
(Chroot l s h) &^ p = Chroot l s (h &^ p) (Chroot l s c h) &^ p = Chroot l s c (h &^ p)
getHost (Chroot _ _ h) = h getHost (Chroot _ _ _ h) = h
-- | Defines a Chroot at the given location, containing the specified -- | Defines a Chroot at the given location, built with debootstrap.
-- System. Properties can be added to configure the Chroot.
-- --
-- > chroot "/srv/chroot/ghc-dev" (System (Debian Unstable) "amd64") -- Properties can be added to configure the Chroot.
-- > & Apt.installed ["build-essential", "ghc", "haskell-platform"] --
-- > debootstrapped (System (Debian Unstable) "amd64") Debootstrap.BuildD "/srv/chroot/ghc-dev"
-- > & Apt.installed ["ghc", "haskell-platform"]
-- > & ... -- > & ...
chroot :: FilePath -> System -> Chroot debootstrapped :: System -> Debootstrap.DebootstrapConfig -> FilePath -> Chroot
chroot location system = Chroot location system (Host location [] mempty) debootstrapped system conf location = case system of
(System (Debian _) _) -> mk
(System (Ubuntu _) _) -> mk
where
h = Host location [] mempty
mk = Chroot location system (UsingDeboostrap conf) h
& os system
-- | Ensures that the chroot exists and is provisioned according to its -- | Ensures that the chroot exists and is provisioned according to its
-- properties. -- properties.
@ -36,35 +53,36 @@ chroot location system = Chroot location system (Host location [] mempty)
-- Reverting this property removes the chroot. Note that it does not ensure -- Reverting this property removes the chroot. Note that it does not ensure
-- that any processes that might be running inside the chroot are stopped. -- that any processes that might be running inside the chroot are stopped.
provisioned :: Chroot -> RevertableProperty provisioned :: Chroot -> RevertableProperty
provisioned c@(Chroot loc system _) = RevertableProperty provisioned c = provisioned' (propigateChrootInfo c) c False
(propigateChrootInfo c (go "exists" setup))
provisioned' :: (Property -> Property) -> Chroot -> Bool -> RevertableProperty
provisioned' propigator c@(Chroot loc system builderconf _) systemdonly = RevertableProperty
(propigator $ go "exists" setup)
(go "removed" teardown) (go "removed" teardown)
where where
go desc a = property (chrootDesc c desc) $ ensureProperties [a] go desc a = property (chrootDesc c desc) $ ensureProperties [a]
setup = provisionChroot c `requires` built setup = propellChroot c (inChrootProcess c) systemdonly
`requires` toProp built
built = case system of built = case (system, builderconf) of
(System (Debian _) _) -> debootstrap ((System (Debian _) _), UsingDeboostrap cf) -> debootstrap cf
(System (Ubuntu _) _) -> debootstrap ((System (Ubuntu _) _), UsingDeboostrap cf) -> debootstrap cf
debootstrap = toProp (Debootstrap.built loc system []) debootstrap = Debootstrap.built loc system
teardown = undefined teardown = toProp (revert built)
propigateChrootInfo :: Chroot -> Property -> Property propigateChrootInfo :: Chroot -> Property -> Property
propigateChrootInfo c p = propigateInfo c p (<> chrootInfo c) propigateChrootInfo c p = propigateInfo c p (<> chrootInfo c)
chrootInfo :: Chroot -> Info chrootInfo :: Chroot -> Info
chrootInfo (Chroot loc _ h) = chrootInfo (Chroot loc _ _ h) =
mempty { _chrootinfo = mempty { _chroots = M.singleton loc h } } mempty { _chrootinfo = mempty { _chroots = M.singleton loc h } }
-- | Propellor is run inside the chroot to provision it. -- | Propellor is run inside the chroot to provision it.
-- propellChroot :: Chroot -> ([String] -> CreateProcess) -> Bool -> Property
-- Strange and wonderful tricks let the host's /usr/local/propellor propellChroot c@(Chroot loc _ _ _) mkproc systemdonly = property (chrootDesc c "provisioned") $ do
-- be used inside the chroot, without needing to install anything.
provisionChroot :: Chroot -> Property
provisionChroot c@(Chroot loc _ _) = property (chrootDesc c "provisioned") $ do
let d = localdir </> shimdir c let d = localdir </> shimdir c
let me = localdir </> "propellor" let me = localdir </> "propellor"
shim <- liftIO $ ifM (doesDirectoryExist d) shim <- liftIO $ ifM (doesDirectoryExist d)
@ -89,42 +107,50 @@ provisionChroot c@(Chroot loc _ _) = property (chrootDesc c "provisioned") $ do
chainprovision shim = do chainprovision shim = do
parenthost <- asks hostName parenthost <- asks hostName
let p = inChrootProcess c cmd <- liftIO $ toChain parenthost c systemdonly
let p = mkproc
[ shim [ shim
, "--continue" , "--continue"
, show $ toChain parenthost c , show cmd
] ]
liftIO $ withHandle StdoutHandle createProcessSuccess p liftIO $ withHandle StdoutHandle createProcessSuccess p
processChainOutput processChainOutput
toChain :: HostName -> Chroot -> CmdLine toChain :: HostName -> Chroot -> Bool -> IO CmdLine
toChain parenthost (Chroot loc _ _) = ChrootChain parenthost loc toChain parenthost (Chroot loc _ _ _) systemdonly = do
onconsole <- isConsole <$> mkMessageHandle
return $ ChrootChain parenthost loc systemdonly onconsole
chain :: [Host] -> HostName -> FilePath -> IO () chain :: [Host] -> CmdLine -> IO ()
chain hostlist hn loc = case findHostNoAlias hostlist hn of chain hostlist (ChrootChain hn loc systemdonly onconsole) =
Nothing -> errorMessage ("cannot find host " ++ hn) case findHostNoAlias hostlist hn of
Just parenthost -> case M.lookup loc (_chroots $ _chrootinfo $ hostInfo parenthost) of Nothing -> errorMessage ("cannot find host " ++ hn)
Nothing -> errorMessage ("cannot find chroot " ++ loc ++ " on host " ++ hn) Just parenthost -> case M.lookup loc (_chroots $ _chrootinfo $ hostInfo parenthost) of
Just h -> go h Nothing -> errorMessage ("cannot find chroot " ++ loc ++ " on host " ++ hn)
Just h -> go h
where where
go h = do go h = do
changeWorkingDirectory localdir changeWorkingDirectory localdir
forceConsole when onconsole forceConsole
onlyProcess (provisioningLock loc) $ do onlyProcess (provisioningLock loc) $ do
r <- runPropellor h $ ensureProperties $ hostProperties h r <- runPropellor h $ ensureProperties $
if systemdonly
then [Systemd.installed]
else hostProperties h
putStrLn $ "\n" ++ show r putStrLn $ "\n" ++ show r
chain _ _ = errorMessage "bad chain command"
inChrootProcess :: Chroot -> [String] -> CreateProcess inChrootProcess :: Chroot -> [String] -> CreateProcess
inChrootProcess (Chroot loc _ _) cmd = proc "chroot" (loc:cmd) inChrootProcess (Chroot loc _ _ _) cmd = proc "chroot" (loc:cmd)
provisioningLock :: FilePath -> FilePath provisioningLock :: FilePath -> FilePath
provisioningLock containerloc = "chroot" </> mungeloc containerloc ++ ".lock" provisioningLock containerloc = "chroot" </> mungeloc containerloc ++ ".lock"
shimdir :: Chroot -> FilePath shimdir :: Chroot -> FilePath
shimdir (Chroot loc _ _) = "chroot" </> mungeloc loc ++ ".shim" shimdir (Chroot loc _ _ _) = "chroot" </> mungeloc loc ++ ".shim"
mungeloc :: FilePath -> String mungeloc :: FilePath -> String
mungeloc = replace "/" "_" mungeloc = replace "/" "_"
chrootDesc :: Chroot -> String -> String chrootDesc :: Chroot -> String -> String
chrootDesc (Chroot loc _ _) desc = "chroot " ++ loc ++ " " ++ desc chrootDesc (Chroot loc _ _ _) desc = "chroot " ++ loc ++ " " ++ desc

View File

@ -1,5 +1,6 @@
module Propellor.Property.Debootstrap ( module Propellor.Property.Debootstrap (
Url, Url,
DebootstrapConfig(..),
built, built,
installed, installed,
programPath, programPath,
@ -15,9 +16,31 @@ import Data.List
import Data.Char import Data.Char
import Control.Exception import Control.Exception
import System.Posix.Directory import System.Posix.Directory
import System.Posix.Files
type Url = String type Url = String
-- | A monoid for debootstrap configuration.
-- mempty is a default debootstrapped system.
data DebootstrapConfig
= DefaultConfig
| MinBase
| BuilddD
| DebootstrapParam String
| DebootstrapConfig :+ DebootstrapConfig
deriving (Show)
instance Monoid DebootstrapConfig where
mempty = DefaultConfig
mappend = (:+)
toParams :: DebootstrapConfig -> [CommandParam]
toParams DefaultConfig = []
toParams MinBase = [Param "--variant=minbase"]
toParams BuilddD = [Param "--variant=buildd"]
toParams (DebootstrapParam p) = [Param p]
toParams (c1 :+ c2) = toParams c1 <> toParams c2
-- | Builds a chroot in the given directory using debootstrap. -- | Builds a chroot in the given directory using debootstrap.
-- --
-- The System can be any OS and architecture that debootstrap -- The System can be any OS and architecture that debootstrap
@ -28,8 +51,8 @@ type Url = String
-- --
-- Note that reverting this property does not stop any processes -- Note that reverting this property does not stop any processes
-- currently running in the chroot. -- currently running in the chroot.
built :: FilePath -> System -> [CommandParam] -> RevertableProperty built :: FilePath -> System -> DebootstrapConfig -> RevertableProperty
built target system@(System _ arch) extraparams = built target system@(System _ arch) config =
RevertableProperty setup teardown RevertableProperty setup teardown
where where
setup = check (unpopulated target <||> ispartial) setupprop setup = check (unpopulated target <||> ispartial) setupprop
@ -41,10 +64,15 @@ built target system@(System _ arch) extraparams =
setupprop = property ("debootstrapped " ++ target) $ liftIO $ do setupprop = property ("debootstrapped " ++ target) $ liftIO $ do
createDirectoryIfMissing True target createDirectoryIfMissing True target
-- Don't allow non-root users to see inside the chroot,
-- since doing so can allow them to do various attacks
-- including hard link farming suid programs for later
-- exploitation.
modifyFileMode target (removeModes [otherReadMode, otherExecuteMode, otherWriteMode])
suite <- case extractSuite system of suite <- case extractSuite system of
Nothing -> errorMessage $ "don't know how to debootstrap " ++ show system Nothing -> errorMessage $ "don't know how to debootstrap " ++ show system
Just s -> pure s Just s -> pure s
let params = extraparams ++ let params = toParams config ++
[ Param $ "--arch=" ++ arch [ Param $ "--arch=" ++ arch
, Param suite , Param suite
, Param target , Param target

View File

@ -1,6 +1,11 @@
module Propellor.Property.Systemd ( module Propellor.Property.Systemd (
installed, module Propellor.Property.Systemd.Core,
started,
stopped,
enabled,
disabled,
persistentJournal, persistentJournal,
Container,
container, container,
nspawned, nspawned,
) where ) where
@ -8,44 +13,69 @@ module Propellor.Property.Systemd (
import Propellor import Propellor
import qualified Propellor.Property.Chroot as Chroot import qualified Propellor.Property.Chroot as Chroot
import qualified Propellor.Property.Apt as Apt import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.File as File
import Propellor.Property.Systemd.Core
import Utility.SafeCommand import Utility.SafeCommand
import Utility.FileMode
import Data.List.Utils import Data.List.Utils
type ServiceName = String
type MachineName = String type MachineName = String
type NspawnParam = CommandParam data Container = Container MachineName Chroot.Chroot Host
data Container = Container MachineName System [CommandParam] Host
instance Hostlike Container where instance Hostlike Container where
(Container n s ps h) & p = Container n s ps (h & p) (Container n c h) & p = Container n c (h & p)
(Container n s ps h) &^ p = Container n s ps (h &^ p) (Container n c h) &^ p = Container n c (h &^ p)
getHost (Container _ _ _ h) = h getHost (Container _ _ h) = h
-- dbus is only a Recommends of systemd, but is needed for communication -- | Starts a systemd service.
-- from the systemd inside a container to the one outside, so make sure it started :: ServiceName -> Property
-- gets installed. started n = trivial $ cmdProperty "systemctl" ["start", n]
installed :: Property `describe` ("service " ++ n ++ " started")
installed = Apt.installed ["systemd", "dbus"]
-- | Sets up persistent storage of the journal. -- | Stops a systemd service.
stopped :: ServiceName -> Property
stopped n = trivial $ cmdProperty "systemctl" ["stop", n]
`describe` ("service " ++ n ++ " stopped")
-- | Enables a systemd service.
enabled :: ServiceName -> Property
enabled n = trivial $ cmdProperty "systemctl" ["enable", n]
`describe` ("service " ++ n ++ " enabled")
-- | Disables a systemd service.
disabled :: ServiceName -> Property
disabled n = trivial $ cmdProperty "systemctl" ["disable", n]
`describe` ("service " ++ n ++ " disabled")
-- | Enables persistent storage of the journal.
persistentJournal :: Property persistentJournal :: Property
persistentJournal = check (not <$> doesDirectoryExist dir) $ persistentJournal = check (not <$> doesDirectoryExist dir) $
combineProperties "persistent systetemd journal" combineProperties "persistent systemd journal"
[ cmdProperty "install" ["-d", "-g", "systemd-journal", dir] [ cmdProperty "install" ["-d", "-g", "systemd-journal", dir]
, cmdProperty "setfacl" ["-R", "-nm", "g:adm:rx,d:g:adm:rx", dir] , cmdProperty "setfacl" ["-R", "-nm", "g:adm:rx,d:g:adm:rx", dir]
, started "systemd-journal-flush"
] ]
`requires` Apt.installed ["acl"] `requires` Apt.installed ["acl"]
where where
dir = "/var/log/journal" dir = "/var/log/journal"
-- | Defines a container with a given machine name, containing the specified -- | Defines a container with a given machine name.
-- System. Properties can be added to configure the Container.
-- --
-- > container "webserver" (System (Debian Unstable) "amd64") [] -- Properties can be added to configure the Container.
container :: MachineName -> System -> [NspawnParam] -> Container --
container name system ps = Container name system ps (Host name [] mempty) -- > container "webserver" (Chroot.debootstrapped (System (Debian Unstable) "amd64") mempty)
-- > & Apt.installedRunning "apache2"
-- > & ...
container :: MachineName -> (FilePath -> Chroot.Chroot) -> Container
container name mkchroot = Container name c h
& os system
where
c@(Chroot.Chroot _ system _ _) = mkchroot (containerDir name)
h = Host name [] mempty
-- | Runs a container using systemd-nspawn. -- | Runs a container using systemd-nspawn.
-- --
@ -62,42 +92,82 @@ container name system ps = Container name system ps (Host name [] mempty)
-- Reverting this property stops the container, removes the systemd unit, -- Reverting this property stops the container, removes the systemd unit,
-- and deletes the chroot and all its contents. -- and deletes the chroot and all its contents.
nspawned :: Container -> RevertableProperty nspawned :: Container -> RevertableProperty
nspawned c@(Container name system _ h) = RevertableProperty setup teardown nspawned c@(Container name (Chroot.Chroot loc system builderconf _) h) =
RevertableProperty setup teardown
where where
-- TODO after container is running, use nsenter to enter it setup = combineProperties ("nspawned " ++ name) $
-- and run propellor to finish provisioning. map toProp steps ++ [containerprovisioned]
setup = toProp (nspawnService c) teardown = combineProperties ("not nspawned " ++ name) $
`requires` toProp chrootprovisioned map (toProp . revert) (reverse steps)
steps =
[ enterScript c
, chrootprovisioned
, nspawnService c
]
teardown = toProp (revert (chrootprovisioned)) -- Chroot provisioning is run in systemd-only mode,
`requires` toProp (revert (nspawnService c)) -- which sets up the chroot and ensures systemd and dbus are
-- installed, but does not handle the other provisions.
chrootprovisioned = Chroot.provisioned'
(Chroot.propigateChrootInfo chroot) chroot True
-- When provisioning the chroot, pass a version of the Host -- Use nsenter to enter container and and run propellor to
-- that only has the Property of systemd being installed. -- finish provisioning.
-- This is to avoid starting any daemons in the chroot, containerprovisioned = Chroot.propellChroot chroot
-- which would not run in the container's namespace. (enterContainerProcess c) False
chrootprovisioned = Chroot.provisioned $
Chroot.Chroot (containerDir name) system $ chroot = Chroot.Chroot loc system builderconf h
h { hostProperties = [installed] }
nspawnService :: Container -> RevertableProperty nspawnService :: Container -> RevertableProperty
nspawnService (Container name _ ps _) = RevertableProperty setup teardown nspawnService (Container name _ _) = RevertableProperty setup teardown
where where
service = nspawnServiceName name service = nspawnServiceName name
servicefile = "/etc/systemd/system/multi-user.target.wants" </> service servicefile = "/etc/systemd/system/multi-user.target.wants" </> service
setup = check (not <$> doesFileExist servicefile) $ setup = check (not <$> doesFileExist servicefile) $
combineProperties ("container running " ++ service) started service
[ cmdProperty "systemctl" ["enable", service] `requires` enabled service
, cmdProperty "systemctl" ["start", service]
teardown = check (doesFileExist servicefile) $
disabled service
`requires` stopped service
-- | Installs a "enter-machinename" script that root can use to run a
-- command inside the container.
--
-- This uses nsenter to enter the container, by looking up the pid of the
-- container's init process and using its namespace.
enterScript :: Container -> RevertableProperty
enterScript c@(Container name _ _) = RevertableProperty setup teardown
where
setup = combineProperties ("generated " ++ enterScriptFile c)
[ scriptfile `File.hasContent`
[ "#!/bin/sh"
, "# Generated by propellor"
, "pid=\"$(machinectl show " ++ shellEscape name ++ " -p Leader | cut -d= -f2)\" || true"
, "if [ -n \"$pid\" ]; then"
, "\tnsenter -p -u -n -i -m -t \"$pid\" \"$@\""
, "else"
, "\techo container not running >&2"
, "\texit 1"
, "fi"
] ]
, scriptfile `File.mode` combineModes (readModes ++ executeModes)
]
teardown = File.notPresent scriptfile
scriptfile = enterScriptFile c
-- TODO adjust execStart line to reflect ps enterScriptFile :: Container -> FilePath
enterScriptFile (Container name _ _ ) = "/usr/local/bin/enter-" ++ mungename name
teardown = undefined enterContainerProcess :: Container -> [String] -> CreateProcess
enterContainerProcess = proc . enterScriptFile
nspawnServiceName :: MachineName -> String nspawnServiceName :: MachineName -> ServiceName
nspawnServiceName name = "systemd-nspawn@" ++ name ++ ".service" nspawnServiceName name = "systemd-nspawn@" ++ name ++ ".service"
containerDir :: MachineName -> FilePath containerDir :: MachineName -> FilePath
containerDir name = "/var/lib/container" ++ replace "/" "_" name containerDir name = "/var/lib/container" </> mungename name
mungename :: MachineName -> String
mungename = replace "/" "_"

View File

@ -0,0 +1,10 @@
module Propellor.Property.Systemd.Core where
import Propellor
import qualified Propellor.Property.Apt as Apt
-- dbus is only a Recommends of systemd, but is needed for communication
-- from the systemd inside a container to the one outside, so make sure it
-- gets installed.
installed :: Property
installed = Apt.installed ["systemd", "dbus"]

View File

@ -155,7 +155,7 @@ data CmdLine
| Update HostName | Update HostName
| DockerInit HostName | DockerInit HostName
| DockerChain HostName String | DockerChain HostName String
| ChrootChain HostName FilePath | ChrootChain HostName FilePath Bool Bool
| GitPush Fd Fd | GitPush Fd Fd
deriving (Read, Show, Eq) deriving (Read, Show, Eq)