2014-04-01 05:12:05 +00:00
|
|
|
{-# LANGUAGE RankNTypes #-}
|
|
|
|
|
2014-04-01 19:26:34 +00:00
|
|
|
-- | Docker support for propellor
|
|
|
|
--
|
|
|
|
-- The existance of a docker container is just another Property of a system,
|
|
|
|
-- which propellor can set up. See config.hs for an example.
|
|
|
|
--
|
|
|
|
-- Note that propellor provisions a container by running itself, inside the
|
|
|
|
-- container. Currently, to avoid the overhead of building propellor
|
|
|
|
-- inside the container, the binary from outside is reused inside.
|
|
|
|
-- So, the libraries that propellor is linked against need to be available
|
|
|
|
-- in the container with compatable versions. This can cause a problem
|
|
|
|
-- if eg, mixing Debian stable and unstable.
|
|
|
|
|
2014-03-31 03:37:54 +00:00
|
|
|
module Propellor.Property.Docker where
|
2014-03-31 01:01:18 +00:00
|
|
|
|
2014-03-31 03:55:59 +00:00
|
|
|
import Propellor
|
2014-04-01 07:48:45 +00:00
|
|
|
import Propellor.SimpleSh
|
2014-03-31 03:37:54 +00:00
|
|
|
import qualified Propellor.Property.File as File
|
|
|
|
import qualified Propellor.Property.Apt as Apt
|
2014-04-01 05:12:05 +00:00
|
|
|
import Utility.SafeCommand
|
2014-04-01 17:51:58 +00:00
|
|
|
import Utility.Path
|
|
|
|
|
|
|
|
import Control.Concurrent.Async
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
dockercmd :: String
|
|
|
|
dockercmd = "docker.io"
|
2014-03-31 01:01:18 +00:00
|
|
|
|
2014-03-31 03:59:07 +00:00
|
|
|
-- | Configures docker with an authentication file, so that images can be
|
|
|
|
-- pushed to index.docker.io.
|
2014-03-31 01:01:18 +00:00
|
|
|
configured :: Property
|
2014-03-31 01:03:42 +00:00
|
|
|
configured = Property "docker configured" go `requires` installed
|
|
|
|
where
|
|
|
|
go = withPrivData DockerAuthentication $ \cfg -> ensureProperty $
|
|
|
|
"/root/.dockercfg" `File.hasContent` (lines cfg)
|
2014-04-01 05:12:05 +00:00
|
|
|
|
2014-03-31 01:03:42 +00:00
|
|
|
installed :: Property
|
|
|
|
installed = Apt.installed ["docker.io"]
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
-- | Parameters to pass to `docker run` when creating a container.
|
|
|
|
type RunParam = String
|
|
|
|
|
|
|
|
data Containerized a = Containerized [RunParam] a
|
|
|
|
|
|
|
|
getRunParams :: [Containerized a] -> [RunParam]
|
|
|
|
getRunParams l = concatMap get l
|
|
|
|
where
|
|
|
|
get (Containerized ps _) = ps
|
|
|
|
|
|
|
|
fromContainerized :: forall a. [Containerized a] -> [a]
|
|
|
|
fromContainerized l = map get l
|
|
|
|
where
|
|
|
|
get (Containerized _ a) = a
|
|
|
|
|
|
|
|
-- | A docker image, that can be used to run a container.
|
|
|
|
type Image = String
|
|
|
|
|
2014-04-01 07:48:45 +00:00
|
|
|
-- | A short descriptive name for a container.
|
2014-04-01 16:43:23 +00:00
|
|
|
-- Should not contain whitespace or other unusual characters,
|
|
|
|
-- only [a-zA-Z0-9_.-] are allowed
|
2014-04-01 05:12:05 +00:00
|
|
|
type ContainerName = String
|
|
|
|
|
|
|
|
-- | A container is identified by its name, and the host
|
|
|
|
-- on which it's deployed.
|
|
|
|
data ContainerId = ContainerId HostName ContainerName
|
2014-04-01 17:04:24 +00:00
|
|
|
deriving (Eq)
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
toContainerId :: String -> Maybe ContainerId
|
2014-04-01 16:43:23 +00:00
|
|
|
toContainerId s = case separate (== '.') s of
|
2014-04-01 05:12:05 +00:00
|
|
|
(cn, hn)
|
|
|
|
| null hn || null cn -> Nothing
|
|
|
|
| otherwise -> Just $ ContainerId hn cn
|
|
|
|
|
|
|
|
fromContainerId :: ContainerId -> String
|
2014-04-01 16:43:23 +00:00
|
|
|
fromContainerId (ContainerId hn cn) = cn++"."++hn
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
data Container = Container Image [Containerized Property]
|
|
|
|
|
2014-04-01 16:42:24 +00:00
|
|
|
containerFrom :: Image -> [Containerized Property] -> Container
|
|
|
|
containerFrom = Container
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
containerProperties
|
|
|
|
:: (HostName -> ContainerName -> Maybe (Container))
|
|
|
|
-> (HostName -> Maybe [Property])
|
|
|
|
containerProperties findcontainer = \h -> case toContainerId h of
|
|
|
|
Nothing -> Nothing
|
2014-04-01 18:20:59 +00:00
|
|
|
Just cid@(ContainerId hn cn) ->
|
2014-04-01 05:12:05 +00:00
|
|
|
case findcontainer hn cn of
|
|
|
|
Nothing -> Nothing
|
|
|
|
Just (Container _ cprops) ->
|
2014-04-01 18:20:59 +00:00
|
|
|
Just $ map (containerDesc cid) $
|
|
|
|
fromContainerized cprops
|
2014-04-01 05:12:05 +00:00
|
|
|
|
2014-04-01 18:20:59 +00:00
|
|
|
containerDesc :: ContainerId -> Property -> Property
|
|
|
|
containerDesc cid p = p `describe` desc
|
|
|
|
where
|
|
|
|
desc = "docker container " ++ fromContainerId cid ++ " " ++ propertyDesc p
|
2014-04-01 17:51:58 +00:00
|
|
|
|
2014-04-01 05:12:05 +00:00
|
|
|
-- | Ensures that a docker container is set up and running. The container
|
|
|
|
-- has its own Properties which are handled by running propellor
|
|
|
|
-- inside the container.
|
2014-04-01 20:58:11 +00:00
|
|
|
docked
|
|
|
|
:: (HostName -> ContainerName -> Maybe (Container))
|
|
|
|
-> HostName
|
2014-04-01 05:12:05 +00:00
|
|
|
-> ContainerName
|
|
|
|
-> Property
|
2014-04-01 20:58:11 +00:00
|
|
|
docked findcontainer hn cn =
|
2014-04-01 05:12:05 +00:00
|
|
|
case findcontainer hn cn of
|
2014-04-01 18:20:59 +00:00
|
|
|
Nothing -> containerDesc cid $ Property "" $ do
|
2014-04-01 05:12:05 +00:00
|
|
|
warningMessage $ "missing definition for docker container \"" ++ fromContainerId cid
|
|
|
|
return FailedChange
|
|
|
|
Just (Container image containerprops) ->
|
2014-04-01 17:51:58 +00:00
|
|
|
provisionContainer cid
|
|
|
|
`requires`
|
|
|
|
runningContainer cid image containerprops
|
2014-04-01 05:12:05 +00:00
|
|
|
where
|
|
|
|
cid = ContainerId hn cn
|
|
|
|
|
2014-04-01 17:51:58 +00:00
|
|
|
runningContainer :: ContainerId -> Image -> [Containerized Property] -> Property
|
2014-04-01 18:20:59 +00:00
|
|
|
runningContainer cid@(ContainerId hn cn) image containerprops = containerDesc cid $ Property "running" $ do
|
2014-04-01 17:04:24 +00:00
|
|
|
l <- listContainers RunningContainers
|
2014-04-01 07:48:45 +00:00
|
|
|
if cid `elem` l
|
|
|
|
then do
|
|
|
|
runningident <- getrunningident
|
|
|
|
if runningident == Just ident
|
|
|
|
then return NoChange
|
|
|
|
else do
|
|
|
|
void $ stopContainer cid
|
|
|
|
oldimage <- fromMaybe image <$> commitContainer cid
|
|
|
|
removeContainer cid
|
|
|
|
go oldimage
|
|
|
|
else do
|
2014-04-01 17:04:24 +00:00
|
|
|
whenM (elem cid <$> listContainers AllContainers) $
|
2014-04-01 16:37:57 +00:00
|
|
|
removeContainer cid
|
2014-04-01 07:48:45 +00:00
|
|
|
go image
|
|
|
|
where
|
2014-04-01 17:04:24 +00:00
|
|
|
ident = ContainerIdent image hn cn runps
|
2014-04-01 07:48:45 +00:00
|
|
|
|
2014-04-01 17:51:58 +00:00
|
|
|
getrunningident = catchDefaultIO Nothing $
|
|
|
|
simpleShClient (namedPipe cid) "cat" [propellorIdent] $
|
|
|
|
pure . headMaybe . catMaybes . map readish . catMaybes . map getStdout
|
2014-04-01 07:48:45 +00:00
|
|
|
|
|
|
|
runps = getRunParams $ containerprops ++
|
|
|
|
-- expose propellor directory inside the container
|
|
|
|
[ volume (localdir++":"++localdir)
|
|
|
|
-- name the container in a predictable way so we
|
|
|
|
-- and the user can easily find it later
|
|
|
|
, name (fromContainerId cid)
|
|
|
|
-- cd to propellor directory
|
|
|
|
, workdir localdir
|
|
|
|
]
|
|
|
|
|
2014-04-01 18:00:46 +00:00
|
|
|
chaincmd = ["./propellor", "--continue", show $ ChainDocker $ show ident]
|
2014-04-01 17:58:15 +00:00
|
|
|
|
|
|
|
go img = ifM (runContainer img (runps ++ ["-i", "-d", "-t"]) chaincmd)
|
2014-04-01 17:51:58 +00:00
|
|
|
( return MadeChange
|
2014-04-01 07:48:45 +00:00
|
|
|
, return FailedChange
|
|
|
|
)
|
|
|
|
|
2014-04-01 17:51:58 +00:00
|
|
|
-- | Two containers with the same ContainerIdent were started from
|
|
|
|
-- the same base image (possibly a different version though), and
|
|
|
|
-- with the same RunParams.
|
|
|
|
data ContainerIdent = ContainerIdent Image HostName ContainerName [RunParam]
|
|
|
|
deriving (Read, Show, Eq)
|
|
|
|
|
|
|
|
-- | The ContainerIdent of a container is written to
|
|
|
|
-- /.propellor-ident inside it. This can be checked to see if
|
|
|
|
-- the container has the same ident later.
|
|
|
|
propellorIdent :: FilePath
|
|
|
|
propellorIdent = "/.propellor-ident"
|
|
|
|
|
|
|
|
-- | Named pipe used for communication with the container.
|
|
|
|
namedPipe :: ContainerId -> FilePath
|
|
|
|
namedPipe cid = "docker/" ++ fromContainerId cid
|
|
|
|
|
|
|
|
-- | Called when propellor is running inside a docker container.
|
|
|
|
-- The string should be the container's ContainerIdent.
|
|
|
|
--
|
|
|
|
-- Fork a thread to run the SimpleSh server in the background.
|
|
|
|
-- In the foreground, run an interactive bash (or sh) shell,
|
|
|
|
-- so that the user can interact with it when attached to the container.
|
|
|
|
chain :: String -> IO ()
|
|
|
|
chain s = case readish s of
|
|
|
|
Nothing -> error $ "Invalid ContainerId: " ++ s
|
|
|
|
Just ident@(ContainerIdent _image hn cn _rp) -> do
|
|
|
|
let cid = ContainerId hn cn
|
|
|
|
writeFile propellorIdent (show ident)
|
2014-04-01 19:38:32 +00:00
|
|
|
void $ async $ simpleSh $ namedPipe cid
|
|
|
|
forever $ do
|
|
|
|
void $ ifM (inPath "bash")
|
|
|
|
( boolSystem "bash" [Param "-l"]
|
|
|
|
, boolSystem "/bin/sh" []
|
|
|
|
)
|
|
|
|
putStrLn "Container is still running. Press ^P^Q to detach."
|
2014-04-01 17:51:58 +00:00
|
|
|
|
|
|
|
-- | Once a container is running, propellor can be run inside
|
|
|
|
-- it to provision it.
|
|
|
|
--
|
|
|
|
-- Note that there is a race here, between the simplesh
|
|
|
|
-- server starting up in the container, and this property
|
|
|
|
-- being run. So, retry connections to the client for up to
|
|
|
|
-- 1 minute.
|
|
|
|
provisionContainer :: ContainerId -> Property
|
2014-04-01 18:20:59 +00:00
|
|
|
provisionContainer cid = containerDesc cid $ Property "provision" $
|
2014-04-01 18:28:05 +00:00
|
|
|
simpleShClientRetry 60 (namedPipe cid) "./propellor" params (go Nothing)
|
2014-04-01 07:48:45 +00:00
|
|
|
where
|
2014-04-01 18:28:05 +00:00
|
|
|
params = ["--continue", show $ Chain $ fromContainerId cid]
|
2014-04-01 07:48:45 +00:00
|
|
|
|
|
|
|
go lastline (v:rest) = case v of
|
|
|
|
StdoutLine s -> do
|
2014-04-01 18:33:03 +00:00
|
|
|
debug ["stdout: ", show s]
|
2014-04-01 07:48:45 +00:00
|
|
|
maybe noop putStrLn lastline
|
|
|
|
hFlush stdout
|
|
|
|
go (Just s) rest
|
|
|
|
StderrLine s -> do
|
2014-04-01 18:33:03 +00:00
|
|
|
debug ["stderr: ", show s]
|
2014-04-01 07:48:45 +00:00
|
|
|
maybe noop putStrLn lastline
|
|
|
|
hFlush stdout
|
|
|
|
hPutStrLn stderr s
|
|
|
|
hFlush stderr
|
|
|
|
go Nothing rest
|
|
|
|
Done _ -> ret lastline
|
|
|
|
go lastline [] = ret lastline
|
|
|
|
|
|
|
|
ret lastline = return $ fromMaybe FailedChange $
|
|
|
|
readish =<< lastline
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
stopContainer :: ContainerId -> IO Bool
|
|
|
|
stopContainer cid = boolSystem dockercmd [Param "stop", Param $ fromContainerId cid ]
|
|
|
|
|
|
|
|
removeContainer :: ContainerId -> IO ()
|
2014-04-01 17:06:50 +00:00
|
|
|
removeContainer cid = void $ catchMaybeIO $
|
2014-04-01 17:07:55 +00:00
|
|
|
readProcess dockercmd ["rm", fromContainerId cid ]
|
2014-04-01 05:12:05 +00:00
|
|
|
|
2014-04-01 16:54:51 +00:00
|
|
|
runContainer :: Image -> [RunParam] -> [String] -> IO Bool
|
2014-04-01 07:48:45 +00:00
|
|
|
runContainer image ps cmd = boolSystem dockercmd $ map Param $
|
2014-04-01 16:54:51 +00:00
|
|
|
"run" : (ps ++ image : cmd)
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
commitContainer :: ContainerId -> IO (Maybe Image)
|
|
|
|
commitContainer cid = catchMaybeIO $
|
2014-04-01 07:48:45 +00:00
|
|
|
takeWhile (/= '\n')
|
|
|
|
<$> readProcess dockercmd ["commit", fromContainerId cid]
|
2014-04-01 05:12:05 +00:00
|
|
|
|
2014-04-01 17:04:24 +00:00
|
|
|
data ContainerFilter = RunningContainers | AllContainers
|
2014-04-01 16:37:57 +00:00
|
|
|
deriving (Eq)
|
|
|
|
|
2014-04-01 05:12:05 +00:00
|
|
|
-- | Only lists propellor managed containers.
|
2014-04-01 17:04:24 +00:00
|
|
|
listContainers :: ContainerFilter -> IO [ContainerId]
|
2014-04-01 16:37:57 +00:00
|
|
|
listContainers status =
|
2014-04-01 17:04:24 +00:00
|
|
|
catMaybes . map toContainerId . catMaybes . map (lastMaybe . words) . lines
|
2014-04-01 16:37:57 +00:00
|
|
|
<$> readProcess dockercmd ps
|
|
|
|
where
|
|
|
|
ps
|
2014-04-01 17:04:24 +00:00
|
|
|
| status == AllContainers = baseps ++ ["--all"]
|
2014-04-01 16:37:57 +00:00
|
|
|
| otherwise = baseps
|
|
|
|
baseps = ["ps", "--no-trunc"]
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
runProp :: String -> RunParam -> Containerized Property
|
2014-04-01 16:37:57 +00:00
|
|
|
runProp field val =
|
2014-04-01 18:20:59 +00:00
|
|
|
Containerized ["--" ++ param] (Property (param) (return NoChange))
|
2014-04-01 05:12:05 +00:00
|
|
|
where
|
|
|
|
param = field++"="++val
|
|
|
|
|
|
|
|
-- | Lift a Property to run inside the container.
|
2014-04-01 15:59:48 +00:00
|
|
|
inside1 :: Property -> Containerized Property
|
|
|
|
inside1 = Containerized []
|
|
|
|
|
|
|
|
inside :: [Property] -> Containerized Property
|
|
|
|
inside = Containerized [] . combineProperties
|
2014-04-01 05:12:05 +00:00
|
|
|
|
|
|
|
-- | Set custom dns server for container.
|
|
|
|
dns :: String -> Containerized Property
|
|
|
|
dns = runProp "dns"
|
|
|
|
|
|
|
|
-- | Set container host name.
|
|
|
|
hostname :: String -> Containerized Property
|
|
|
|
hostname = runProp "hostname"
|
|
|
|
|
|
|
|
-- | Set name for container. (Normally done automatically.)
|
|
|
|
name :: String -> Containerized Property
|
|
|
|
name = runProp "name"
|
|
|
|
|
|
|
|
-- | Publish a container's port to the host
|
|
|
|
-- (format: ip:hostPort:containerPort | ip::containerPort | hostPort:containerPort)
|
|
|
|
publish :: String -> Containerized Property
|
|
|
|
publish = runProp "publish"
|
|
|
|
|
|
|
|
-- | Username or UID for container.
|
|
|
|
user :: String -> Containerized Property
|
|
|
|
user = runProp "user"
|
|
|
|
|
|
|
|
-- | Bind mount a volume
|
|
|
|
volume :: String -> Containerized Property
|
|
|
|
volume = runProp "volume"
|
|
|
|
|
|
|
|
-- | Work dir inside the container.
|
|
|
|
-- Must contain ./propellor! (Normally set automatically.)
|
|
|
|
workdir :: String -> Containerized Property
|
|
|
|
workdir = runProp "workdir"
|
|
|
|
|
|
|
|
-- | Memory limit for container.
|
|
|
|
--Format: <number><optional unit>, where unit = b, k, m or g
|
|
|
|
memory :: String -> Containerized Property
|
|
|
|
memory = runProp "memory"
|