Merge branch 'joeyconfig'
This commit is contained in:
commit
1eaeddc2eb
|
@ -24,7 +24,7 @@ import qualified Propellor.Property.Postfix as Postfix
|
|||
import qualified Propellor.Property.Grub as Grub
|
||||
import qualified Propellor.Property.Obnam as Obnam
|
||||
import qualified Propellor.Property.Gpg as Gpg
|
||||
import qualified Propellor.Property.Debootstrap as Debootstrap
|
||||
import qualified Propellor.Property.Chroot as Chroot
|
||||
import qualified Propellor.Property.HostingProvider.DigitalOcean as DigitalOcean
|
||||
import qualified Propellor.Property.HostingProvider.CloudAtCost as CloudAtCost
|
||||
import qualified Propellor.Property.HostingProvider.Linode as Linode
|
||||
|
@ -80,8 +80,12 @@ clam = standardSystem "clam.kitenet.net" Unstable "amd64"
|
|||
! Ssh.listenPort 80
|
||||
! Ssh.listenPort 443
|
||||
|
||||
! Debootstrap.built "/tmp/chroot" (System (Debian Unstable) "amd64") []
|
||||
& Chroot.provisioned testChroot
|
||||
|
||||
testChroot :: Chroot.Chroot
|
||||
testChroot = Chroot.chroot "/tmp/chroot" (System (Debian Unstable) "amd64")
|
||||
& File.hasContent "/foo" ["hello"]
|
||||
|
||||
orca :: Host
|
||||
orca = standardSystem "orca.kitenet.net" Unstable "amd64"
|
||||
[ "Main git-annex build box." ]
|
||||
|
|
|
@ -19,6 +19,9 @@ propellor (1.0.0) UNRELEASED; urgency=medium
|
|||
in the main host list, and are instead passed to
|
||||
Docker.docked. (API change)
|
||||
* Added support for using debootstrap from propellor.
|
||||
* Propellor can now be used to provision chroots.
|
||||
* systemd-nspawn containers can now be managed by propellor, very similar
|
||||
to its handling of docker containers.
|
||||
|
||||
-- Joey Hess <id@joeyh.name> Mon, 10 Nov 2014 11:15:27 -0400
|
||||
|
||||
|
|
|
@ -0,0 +1,4 @@
|
|||
Aggregating propellor blog posts etc..
|
||||
|
||||
* [[!aggregate expirecount=25 name="joey" feedurl="http://joeyh.name/blog/propellor/" url="http://joeyh.name/blog/propellor/index.rss"]]
|
||||
|
|
@ -31,3 +31,7 @@ You are encouraged to send patches and improve it. See [[contributing]].
|
|||
## news
|
||||
|
||||
[[!inline pages="news/* and !*/Discussion" show="4" archive=yes]]
|
||||
|
||||
## feeds
|
||||
|
||||
[[!inline pages="feeds/* and !*/Discussion" show="4" archive=yes]]
|
||||
|
|
|
@ -74,6 +74,7 @@ Library
|
|||
Propellor.Property.Apt
|
||||
Propellor.Property.Cmd
|
||||
Propellor.Property.Hostname
|
||||
Propellor.Property.Chroot
|
||||
Propellor.Property.Cron
|
||||
Propellor.Property.Debootstrap
|
||||
Propellor.Property.Dns
|
||||
|
@ -94,6 +95,7 @@ Library
|
|||
Propellor.Property.Service
|
||||
Propellor.Property.Ssh
|
||||
Propellor.Property.Sudo
|
||||
Propellor.Property.Systemd
|
||||
Propellor.Property.Tor
|
||||
Propellor.Property.User
|
||||
Propellor.Property.HostingProvider.CloudAtCost
|
||||
|
@ -102,6 +104,7 @@ Library
|
|||
Propellor.Property.SiteSpecific.GitHome
|
||||
Propellor.Property.SiteSpecific.JoeySites
|
||||
Propellor.Property.SiteSpecific.GitAnnexBuilder
|
||||
Propellor.Host
|
||||
Propellor.CmdLine
|
||||
Propellor.Info
|
||||
Propellor.Message
|
||||
|
@ -119,7 +122,7 @@ Library
|
|||
Propellor.Ssh
|
||||
Propellor.PrivData.Paths
|
||||
Propellor.Protocol
|
||||
Propellor.Property.Docker.Shim
|
||||
Propellor.Shim
|
||||
Utility.Applicative
|
||||
Utility.Data
|
||||
Utility.Directory
|
||||
|
|
|
@ -33,6 +33,7 @@ module Propellor (
|
|||
module Propellor.Types
|
||||
, module Propellor.Property
|
||||
, module Propellor.Property.Cmd
|
||||
, module Propellor.Host
|
||||
, module Propellor.Info
|
||||
, module Propellor.PrivData
|
||||
, module Propellor.Engine
|
||||
|
@ -51,6 +52,7 @@ import Propellor.PrivData
|
|||
import Propellor.Message
|
||||
import Propellor.Exception
|
||||
import Propellor.Info
|
||||
import Propellor.Host
|
||||
|
||||
import Utility.PartialPrelude as X
|
||||
import Utility.Process as X
|
||||
|
|
|
@ -15,7 +15,8 @@ import Propellor.Git
|
|||
import Propellor.Ssh
|
||||
import Propellor.Server
|
||||
import qualified Propellor.Property.Docker as Docker
|
||||
import qualified Propellor.Property.Docker.Shim as DockerShim
|
||||
import qualified Propellor.Property.Chroot as Chroot
|
||||
import qualified Propellor.Shim as Shim
|
||||
import Utility.SafeCommand
|
||||
|
||||
usage :: Handle -> IO ()
|
||||
|
@ -72,7 +73,7 @@ processCmdLine = go =<< getArgs
|
|||
-- | Runs propellor on hosts, as controlled by command-line options.
|
||||
defaultMain :: [Host] -> IO ()
|
||||
defaultMain hostlist = do
|
||||
DockerShim.cleanEnv
|
||||
Shim.cleanEnv
|
||||
checkDebugMode
|
||||
cmdline <- processCmdLine
|
||||
debug ["command line: ", show cmdline]
|
||||
|
@ -85,6 +86,7 @@ defaultMain hostlist = do
|
|||
go _ ListFields = listPrivDataFields hostlist
|
||||
go _ (AddKey keyid) = addKey keyid
|
||||
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 _ (GitPush fin fout) = gitPushHelper fin fout
|
||||
go _ (Update _) = forceConsole >> fetchFirst (onlyprocess update)
|
||||
|
|
|
@ -11,12 +11,15 @@ import "mtl" Control.Monad.Reader
|
|||
import Control.Exception (bracket)
|
||||
import System.PosixCompat
|
||||
import System.Posix.IO
|
||||
import Data.Maybe
|
||||
|
||||
import Propellor.Types
|
||||
import Propellor.Message
|
||||
import Propellor.Exception
|
||||
import Propellor.Info
|
||||
import Utility.Exception
|
||||
import Utility.PartialPrelude
|
||||
import Utility.Monad
|
||||
|
||||
runPropellor :: Host -> Propellor a -> IO a
|
||||
runPropellor host a = runReaderT (runWithHost a) host
|
||||
|
@ -62,3 +65,18 @@ onlyProcess lockfile a = bracket lock unlock (const a)
|
|||
return l
|
||||
unlock = closeFd
|
||||
alreadyrunning = error "Propellor is already running on this host!"
|
||||
|
||||
-- | Reads and displays each line from the Handle, except for the last line
|
||||
-- which is a Result.
|
||||
processChainOutput :: Handle -> IO Result
|
||||
processChainOutput h = go Nothing
|
||||
where
|
||||
go lastline = do
|
||||
v <- catchMaybeIO (hGetLine h)
|
||||
case v of
|
||||
Nothing -> pure $ fromMaybe FailedChange $
|
||||
readish =<< lastline
|
||||
Just s -> do
|
||||
maybe noop (\l -> unless (null l) (putStrLn l)) lastline
|
||||
hFlush stdout
|
||||
go (Just s)
|
||||
|
|
|
@ -0,0 +1,64 @@
|
|||
{-# LANGUAGE PackageImports #-}
|
||||
|
||||
module Propellor.Host where
|
||||
|
||||
import Data.Monoid
|
||||
import qualified Data.Set as S
|
||||
|
||||
import Propellor.Types
|
||||
import Propellor.Info
|
||||
import Propellor.Property
|
||||
import Propellor.PrivData
|
||||
|
||||
-- | Starts accumulating the properties of a Host.
|
||||
--
|
||||
-- > host "example.com"
|
||||
-- > & someproperty
|
||||
-- > ! oldproperty
|
||||
-- > & otherproperty
|
||||
host :: HostName -> Host
|
||||
host hn = Host hn [] mempty
|
||||
|
||||
-- | Something that can accumulate properties.
|
||||
class Hostlike h where
|
||||
-- | Adds a property.
|
||||
--
|
||||
-- Can add Properties and RevertableProperties
|
||||
(&) :: IsProp p => h -> p -> h
|
||||
|
||||
-- | Like (&), but adds the property as the
|
||||
-- first property of the host. Normally, property
|
||||
-- order should not matter, but this is useful
|
||||
-- when it does.
|
||||
(&^) :: IsProp p => h -> p -> h
|
||||
|
||||
getHost :: h -> Host
|
||||
|
||||
instance Hostlike Host where
|
||||
(Host hn ps is) & p = Host hn (ps ++ [toProp p]) (is <> getInfo p)
|
||||
(Host hn ps is) &^ p = Host hn ([toProp p] ++ ps) (getInfo p <> is)
|
||||
getHost h = h
|
||||
|
||||
-- | Adds a property in reverted form.
|
||||
(!) :: Hostlike h => h -> RevertableProperty -> h
|
||||
h ! p = h & revert p
|
||||
|
||||
infixl 1 &^
|
||||
infixl 1 &
|
||||
infixl 1 !
|
||||
|
||||
-- | When eg, docking a container, some of the Info about the container
|
||||
-- should propigate out to the Host it's on. This includes DNS info,
|
||||
-- so that eg, aliases of the container are reflected in the dns for the
|
||||
-- host where it runs.
|
||||
--
|
||||
-- This adjusts the Property that docks a container, to include such info
|
||||
-- from the container.
|
||||
propigateInfo :: Hostlike hl => hl -> Property -> (Info -> Info) -> Property
|
||||
propigateInfo hl p f = combineProperties (propertyDesc p) $
|
||||
p' : dnsprops ++ privprops
|
||||
where
|
||||
p' = p { propertyInfo = f (propertyInfo p) }
|
||||
i = hostInfo (getHost hl)
|
||||
dnsprops = map addDNS (S.toList $ _dns i)
|
||||
privprops = map addPrivDataField (S.toList $ _privDataFields i)
|
|
@ -3,6 +3,7 @@
|
|||
module Propellor.Property where
|
||||
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
import Control.Monad
|
||||
import Data.Monoid
|
||||
import Control.Monad.IfElse
|
||||
|
@ -12,7 +13,6 @@ import Propellor.Types
|
|||
import Propellor.Info
|
||||
import Propellor.Engine
|
||||
import Utility.Monad
|
||||
import System.FilePath
|
||||
|
||||
-- Constructs a Property.
|
||||
property :: Desc -> Propellor Result -> Property
|
||||
|
@ -131,42 +131,6 @@ boolProperty desc a = property desc $ ifM (liftIO a)
|
|||
revert :: RevertableProperty -> RevertableProperty
|
||||
revert (RevertableProperty p1 p2) = RevertableProperty p2 p1
|
||||
|
||||
-- | Turns a revertable property into a regular property.
|
||||
unrevertable :: RevertableProperty -> Property
|
||||
unrevertable (RevertableProperty p1 _p2) = p1
|
||||
|
||||
-- | Starts accumulating the properties of a Host.
|
||||
--
|
||||
-- > host "example.com"
|
||||
-- > & someproperty
|
||||
-- > ! oldproperty
|
||||
-- > & otherproperty
|
||||
host :: HostName -> Host
|
||||
host hn = Host hn [] mempty
|
||||
|
||||
class Hostlike h where
|
||||
-- | Adds a property to a Host
|
||||
--
|
||||
-- Can add Properties and RevertableProperties
|
||||
(&) :: IsProp p => h -> p -> h
|
||||
-- | Like (&), but adds the property as the
|
||||
-- first property of the host. Normally, property
|
||||
-- order should not matter, but this is useful
|
||||
-- when it does.
|
||||
(&^) :: IsProp p => h -> p -> h
|
||||
|
||||
instance Hostlike Host where
|
||||
(Host hn ps is) & p = Host hn (ps ++ [toProp p]) (is <> getInfo p)
|
||||
(Host hn ps is) &^ p = Host hn ([toProp p] ++ ps) (getInfo p <> is)
|
||||
|
||||
-- | Adds a property to the Host in reverted form.
|
||||
(!) :: Hostlike h => h -> RevertableProperty -> h
|
||||
h ! p = h & revert p
|
||||
|
||||
infixl 1 &^
|
||||
infixl 1 &
|
||||
infixl 1 !
|
||||
|
||||
-- Changes the action that is performed to satisfy a property.
|
||||
adjustProperty :: Property -> (Propellor Result -> Propellor Result) -> Property
|
||||
adjustProperty p f = p { propertySatisfy = f (propertySatisfy p) }
|
||||
|
|
|
@ -0,0 +1,130 @@
|
|||
module Propellor.Property.Chroot (
|
||||
Chroot(..),
|
||||
chroot,
|
||||
provisioned,
|
||||
chain,
|
||||
) where
|
||||
|
||||
import Propellor
|
||||
import qualified Propellor.Property.Debootstrap as Debootstrap
|
||||
import qualified Propellor.Shim as Shim
|
||||
import Utility.SafeCommand
|
||||
|
||||
import qualified Data.Map as M
|
||||
import Data.List.Utils
|
||||
import System.Posix.Directory
|
||||
|
||||
data Chroot = Chroot FilePath System Host
|
||||
|
||||
instance Hostlike Chroot where
|
||||
(Chroot l s h) & p = Chroot l s (h & p)
|
||||
(Chroot l s h) &^ p = Chroot l s (h &^ p)
|
||||
getHost (Chroot _ _ h) = h
|
||||
|
||||
-- | Defines a Chroot at the given location, containing the specified
|
||||
-- System. Properties can be added to configure the Chroot.
|
||||
--
|
||||
-- > chroot "/srv/chroot/ghc-dev" (System (Debian Unstable) "amd64")
|
||||
-- > & Apt.installed ["build-essential", "ghc", "haskell-platform"]
|
||||
-- > & ...
|
||||
chroot :: FilePath -> System -> Chroot
|
||||
chroot location system = Chroot location system (Host location [] mempty)
|
||||
|
||||
-- | Ensures that the chroot exists and is provisioned according to its
|
||||
-- properties.
|
||||
--
|
||||
-- Reverting this property removes the chroot. Note that it does not ensure
|
||||
-- that any processes that might be running inside the chroot are stopped.
|
||||
provisioned :: Chroot -> RevertableProperty
|
||||
provisioned c@(Chroot loc system _) = RevertableProperty
|
||||
(propigateChrootInfo c (go "exists" setup))
|
||||
(go "removed" teardown)
|
||||
where
|
||||
go desc a = property (chrootDesc c desc) $ ensureProperties [a]
|
||||
|
||||
setup = provisionChroot c `requires` built
|
||||
|
||||
built = case system of
|
||||
(System (Debian _) _) -> debootstrap
|
||||
(System (Ubuntu _) _) -> debootstrap
|
||||
|
||||
debootstrap = toProp (Debootstrap.built loc system [])
|
||||
|
||||
teardown = undefined
|
||||
|
||||
propigateChrootInfo :: Chroot -> Property -> Property
|
||||
propigateChrootInfo c p = propigateInfo c p (<> chrootInfo c)
|
||||
|
||||
chrootInfo :: Chroot -> Info
|
||||
chrootInfo (Chroot loc _ h) =
|
||||
mempty { _chrootinfo = mempty { _chroots = M.singleton loc h } }
|
||||
|
||||
-- | Propellor is run inside the chroot to provision it.
|
||||
--
|
||||
-- Strange and wonderful tricks let the host's /usr/local/propellor
|
||||
-- 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 me = localdir </> "propellor"
|
||||
shim <- liftIO $ ifM (doesDirectoryExist d)
|
||||
( pure (Shim.file me d)
|
||||
, Shim.setup me d
|
||||
)
|
||||
ifM (liftIO $ bindmount shim)
|
||||
( chainprovision shim
|
||||
, return FailedChange
|
||||
)
|
||||
where
|
||||
bindmount shim = ifM (doesFileExist (loc ++ shim))
|
||||
( return True
|
||||
, do
|
||||
let mntpnt = loc ++ localdir
|
||||
createDirectoryIfMissing True mntpnt
|
||||
boolSystem "mount"
|
||||
[ Param "--bind"
|
||||
, File localdir, File mntpnt
|
||||
]
|
||||
)
|
||||
|
||||
chainprovision shim = do
|
||||
parenthost <- asks hostName
|
||||
let p = inChrootProcess c
|
||||
[ shim
|
||||
, "--continue"
|
||||
, show $ toChain parenthost c
|
||||
]
|
||||
liftIO $ withHandle StdoutHandle createProcessSuccess p
|
||||
processChainOutput
|
||||
|
||||
toChain :: HostName -> Chroot -> CmdLine
|
||||
toChain parenthost (Chroot loc _ _) = ChrootChain parenthost loc
|
||||
|
||||
chain :: [Host] -> HostName -> FilePath -> IO ()
|
||||
chain hostlist hn loc = case findHostNoAlias hostlist hn of
|
||||
Nothing -> errorMessage ("cannot find host " ++ hn)
|
||||
Just parenthost -> case M.lookup loc (_chroots $ _chrootinfo $ hostInfo parenthost) of
|
||||
Nothing -> errorMessage ("cannot find chroot " ++ loc ++ " on host " ++ hn)
|
||||
Just h -> go h
|
||||
where
|
||||
go h = do
|
||||
changeWorkingDirectory localdir
|
||||
forceConsole
|
||||
onlyProcess (provisioningLock loc) $ do
|
||||
r <- runPropellor h $ ensureProperties $ hostProperties h
|
||||
putStrLn $ "\n" ++ show r
|
||||
|
||||
inChrootProcess :: Chroot -> [String] -> CreateProcess
|
||||
inChrootProcess (Chroot loc _ _) cmd = proc "chroot" (loc:cmd)
|
||||
|
||||
provisioningLock :: FilePath -> FilePath
|
||||
provisioningLock containerloc = "chroot" </> mungeloc containerloc ++ ".lock"
|
||||
|
||||
shimdir :: Chroot -> FilePath
|
||||
shimdir (Chroot loc _ _) = "chroot" </> mungeloc loc ++ ".shim"
|
||||
|
||||
mungeloc :: FilePath -> String
|
||||
mungeloc = replace "/" "_"
|
||||
|
||||
chrootDesc :: Chroot -> String -> String
|
||||
chrootDesc (Chroot loc _ _) desc = "chroot " ++ loc ++ " " ++ desc
|
|
@ -33,7 +33,7 @@ built target system@(System _ arch) extraparams =
|
|||
RevertableProperty setup teardown
|
||||
where
|
||||
setup = check (unpopulated target <||> ispartial) setupprop
|
||||
`requires` unrevertable installed
|
||||
`requires` toProp installed
|
||||
|
||||
teardown = check (not <$> unpopulated target) teardownprop
|
||||
|
||||
|
|
|
@ -41,7 +41,7 @@ module Propellor.Property.Docker (
|
|||
import Propellor hiding (init)
|
||||
import qualified Propellor.Property.File as File
|
||||
import qualified Propellor.Property.Apt as Apt
|
||||
import qualified Propellor.Property.Docker.Shim as Shim
|
||||
import qualified Propellor.Shim as Shim
|
||||
import Utility.SafeCommand
|
||||
import Utility.Path
|
||||
import Utility.ThreadScheduler
|
||||
|
@ -52,7 +52,6 @@ import System.Posix.Process
|
|||
import Prelude hiding (init)
|
||||
import Data.List hiding (init)
|
||||
import Data.List.Utils
|
||||
import qualified Data.Set as S
|
||||
import qualified Data.Map as M
|
||||
|
||||
installed :: Property
|
||||
|
@ -78,8 +77,10 @@ data Container = Container Image Host
|
|||
instance Hostlike Container where
|
||||
(Container i h) & p = Container i (h & p)
|
||||
(Container i h) &^ p = Container i (h &^ p)
|
||||
getHost (Container _ h) = h
|
||||
|
||||
-- | Builds a Container with a given name, image, and properties.
|
||||
-- | Defines a Container with a given name, image, and properties.
|
||||
-- Properties can be added to configure the Container.
|
||||
--
|
||||
-- > container "web-server" "debian"
|
||||
-- > & publish "80:80"
|
||||
|
@ -100,11 +101,9 @@ container cn image = Container image (Host cn [] info)
|
|||
--
|
||||
-- Reverting this property ensures that the container is stopped and
|
||||
-- removed.
|
||||
docked
|
||||
:: Container
|
||||
-> RevertableProperty
|
||||
docked :: Container -> RevertableProperty
|
||||
docked ctr@(Container _ h) = RevertableProperty
|
||||
(propigateInfo ctr (go "docked" setup))
|
||||
(propigateContainerInfo ctr (go "docked" setup))
|
||||
(go "undocked" teardown)
|
||||
where
|
||||
cn = hostName h
|
||||
|
@ -131,14 +130,12 @@ docked ctr@(Container _ h) = RevertableProperty
|
|||
]
|
||||
]
|
||||
|
||||
propigateInfo :: Container -> Property -> Property
|
||||
propigateInfo (Container _ h@(Host hn _ containerinfo)) p =
|
||||
combineProperties (propertyDesc p) $ p' : dnsprops ++ privprops
|
||||
propigateContainerInfo :: Container -> Property -> Property
|
||||
propigateContainerInfo ctr@(Container _ h) p =
|
||||
propigateInfo ctr p (<> dockerinfo)
|
||||
where
|
||||
p' = p { propertyInfo = propertyInfo p <> dockerinfo }
|
||||
dockerinfo = dockerInfo $ mempty { _dockerContainers = M.singleton hn h }
|
||||
dnsprops = map addDNS (S.toList $ _dns containerinfo)
|
||||
privprops = map addPrivDataField (S.toList $ _privDataFields containerinfo)
|
||||
dockerinfo = dockerInfo $
|
||||
mempty { _dockerContainers = M.singleton (hostName h) h }
|
||||
|
||||
mkContainerInfo :: ContainerId -> Container -> ContainerInfo
|
||||
mkContainerInfo cid@(ContainerId hn _cn) (Container img h) =
|
||||
|
@ -435,20 +432,10 @@ provisionContainer cid = containerDesc cid $ property "provisioned" $ liftIO $ d
|
|||
[ if isConsole msgh then "-it" else "-i" ]
|
||||
(shim : params)
|
||||
r <- withHandle StdoutHandle createProcessSuccess p $
|
||||
processoutput Nothing
|
||||
processChainOutput
|
||||
when (r /= FailedChange) $
|
||||
setProvisionedFlag cid
|
||||
return r
|
||||
where
|
||||
processoutput lastline h = do
|
||||
v <- catchMaybeIO (hGetLine h)
|
||||
case v of
|
||||
Nothing -> pure $ fromMaybe FailedChange $
|
||||
readish =<< lastline
|
||||
Just s -> do
|
||||
maybe noop putStrLn lastline
|
||||
hFlush stdout
|
||||
processoutput (Just s) h
|
||||
|
||||
toChain :: ContainerId -> CmdLine
|
||||
toChain cid = DockerChain (containerHostName cid) (fromContainerId cid)
|
||||
|
|
|
@ -0,0 +1,103 @@
|
|||
module Propellor.Property.Systemd (
|
||||
installed,
|
||||
persistentJournal,
|
||||
container,
|
||||
nspawned,
|
||||
) where
|
||||
|
||||
import Propellor
|
||||
import qualified Propellor.Property.Chroot as Chroot
|
||||
import qualified Propellor.Property.Apt as Apt
|
||||
import Utility.SafeCommand
|
||||
|
||||
import Data.List.Utils
|
||||
|
||||
type MachineName = String
|
||||
|
||||
type NspawnParam = CommandParam
|
||||
|
||||
data Container = Container MachineName System [CommandParam] Host
|
||||
|
||||
instance Hostlike Container where
|
||||
(Container n s ps h) & p = Container n s ps (h & p)
|
||||
(Container n s ps h) &^ p = Container n s ps (h &^ p)
|
||||
getHost (Container _ _ _ h) = h
|
||||
|
||||
-- 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"]
|
||||
|
||||
-- | Sets up persistent storage of the journal.
|
||||
persistentJournal :: Property
|
||||
persistentJournal = check (not <$> doesDirectoryExist dir) $
|
||||
combineProperties "persistent systetemd journal"
|
||||
[ cmdProperty "install" ["-d", "-g", "systemd-journal", dir]
|
||||
, cmdProperty "setfacl" ["-R", "-nm", "g:adm:rx,d:g:adm:rx", dir]
|
||||
]
|
||||
`requires` Apt.installed ["acl"]
|
||||
where
|
||||
dir = "/var/log/journal"
|
||||
|
||||
-- | Defines a container with a given machine name, containing the specified
|
||||
-- System. Properties can be added to configure the Container.
|
||||
--
|
||||
-- > container "webserver" (System (Debian Unstable) "amd64") []
|
||||
container :: MachineName -> System -> [NspawnParam] -> Container
|
||||
container name system ps = Container name system ps (Host name [] mempty)
|
||||
|
||||
-- | Runs a container using systemd-nspawn.
|
||||
--
|
||||
-- A systemd unit is set up for the container, so it will automatically
|
||||
-- be started on boot.
|
||||
--
|
||||
-- Systemd is automatically installed inside the container, and will
|
||||
-- communicate with the host's systemd. This allows systemctl to be used to
|
||||
-- examine the status of services running inside the container.
|
||||
--
|
||||
-- When the host system has persistentJournal enabled, journactl can be
|
||||
-- used to examine logs forwarded from the container.
|
||||
--
|
||||
-- Reverting this property stops the container, removes the systemd unit,
|
||||
-- and deletes the chroot and all its contents.
|
||||
nspawned :: Container -> RevertableProperty
|
||||
nspawned c@(Container name system _ h) = RevertableProperty setup teardown
|
||||
where
|
||||
-- TODO after container is running, use nsenter to enter it
|
||||
-- and run propellor to finish provisioning.
|
||||
setup = toProp (nspawnService c)
|
||||
`requires` toProp chrootprovisioned
|
||||
|
||||
teardown = toProp (revert (chrootprovisioned))
|
||||
`requires` toProp (revert (nspawnService c))
|
||||
|
||||
-- When provisioning the chroot, pass a version of the Host
|
||||
-- that only has the Property of systemd being installed.
|
||||
-- This is to avoid starting any daemons in the chroot,
|
||||
-- which would not run in the container's namespace.
|
||||
chrootprovisioned = Chroot.provisioned $
|
||||
Chroot.Chroot (containerDir name) system $
|
||||
h { hostProperties = [installed] }
|
||||
|
||||
nspawnService :: Container -> RevertableProperty
|
||||
nspawnService (Container name _ ps _) = RevertableProperty setup teardown
|
||||
where
|
||||
service = nspawnServiceName name
|
||||
servicefile = "/etc/systemd/system/multi-user.target.wants" </> service
|
||||
|
||||
setup = check (not <$> doesFileExist servicefile) $
|
||||
combineProperties ("container running " ++ service)
|
||||
[ cmdProperty "systemctl" ["enable", service]
|
||||
, cmdProperty "systemctl" ["start", service]
|
||||
]
|
||||
|
||||
-- TODO adjust execStart line to reflect ps
|
||||
|
||||
teardown = undefined
|
||||
|
||||
nspawnServiceName :: MachineName -> String
|
||||
nspawnServiceName name = "systemd-nspawn@" ++ name ++ ".service"
|
||||
|
||||
containerDir :: MachineName -> FilePath
|
||||
containerDir name = "/var/lib/container" ++ replace "/" "_" name
|
|
@ -1,9 +1,10 @@
|
|||
-- | Support for running propellor, as built outside a docker container,
|
||||
-- inside the container.
|
||||
-- | Support for running propellor, as built outside a container,
|
||||
-- inside the container, without needing to install anything into the
|
||||
-- container.
|
||||
--
|
||||
-- Note: This is currently Debian specific, due to glibcLibs.
|
||||
|
||||
module Propellor.Property.Docker.Shim (setup, cleanEnv, file) where
|
||||
module Propellor.Shim (setup, cleanEnv, file) where
|
||||
|
||||
import Propellor
|
||||
import Utility.LinuxMkLibs
|
|
@ -25,6 +25,7 @@ module Propellor.Types
|
|||
, fromVal
|
||||
, DockerInfo(..)
|
||||
, DockerRunParam(..)
|
||||
, ChrootInfo(..)
|
||||
, module Propellor.Types.OS
|
||||
, module Propellor.Types.Dns
|
||||
) where
|
||||
|
@ -154,6 +155,7 @@ data CmdLine
|
|||
| Update HostName
|
||||
| DockerInit HostName
|
||||
| DockerChain HostName String
|
||||
| ChrootChain HostName FilePath
|
||||
| GitPush Fd Fd
|
||||
deriving (Read, Show, Eq)
|
||||
|
||||
|
@ -166,11 +168,12 @@ data Info = Info
|
|||
, _dns :: S.Set Dns.Record
|
||||
, _namedconf :: Dns.NamedConfMap
|
||||
, _dockerinfo :: DockerInfo
|
||||
, _chrootinfo :: ChrootInfo
|
||||
}
|
||||
deriving (Eq, Show)
|
||||
deriving (Show)
|
||||
|
||||
instance Monoid Info where
|
||||
mempty = Info mempty mempty mempty mempty mempty mempty mempty
|
||||
mempty = Info mempty mempty mempty mempty mempty mempty mempty mempty
|
||||
mappend old new = Info
|
||||
{ _os = _os old <> _os new
|
||||
, _privDataFields = _privDataFields old <> _privDataFields new
|
||||
|
@ -179,6 +182,7 @@ instance Monoid Info where
|
|||
, _dns = _dns old <> _dns new
|
||||
, _namedconf = _namedconf old <> _namedconf new
|
||||
, _dockerinfo = _dockerinfo old <> _dockerinfo new
|
||||
, _chrootinfo = _chrootinfo old <> _chrootinfo new
|
||||
}
|
||||
|
||||
data Val a = Val a | NoVal
|
||||
|
@ -207,13 +211,18 @@ instance Monoid DockerInfo where
|
|||
, _dockerContainers = M.union (_dockerContainers old) (_dockerContainers new)
|
||||
}
|
||||
|
||||
instance Eq DockerInfo where
|
||||
x == y = and
|
||||
[ let simpl v = map (\(DockerRunParam a) -> a "") (_dockerRunParams v)
|
||||
in simpl x == simpl y
|
||||
]
|
||||
|
||||
newtype DockerRunParam = DockerRunParam (HostName -> String)
|
||||
|
||||
instance Show DockerRunParam where
|
||||
show (DockerRunParam a) = a ""
|
||||
|
||||
data ChrootInfo = ChrootInfo
|
||||
{ _chroots :: M.Map FilePath Host
|
||||
}
|
||||
deriving (Show)
|
||||
|
||||
instance Monoid ChrootInfo where
|
||||
mempty = ChrootInfo mempty
|
||||
mappend old new = ChrootInfo
|
||||
{ _chroots = M.union (_chroots old) (_chroots new)
|
||||
}
|
||||
|
|
Loading…
Reference in New Issue