docker support is working in theory (but untested)

This commit is contained in:
Joey Hess 2014-04-01 03:48:45 -04:00
parent 25c4d18503
commit bf4ba05528
3 changed files with 97 additions and 67 deletions

View File

@ -17,6 +17,7 @@ data CmdLine
| AddKey String | AddKey String
| Continue CmdLine | Continue CmdLine
| SimpleSh FilePath | SimpleSh FilePath
| Chain HostName
deriving (Read, Show, Eq) deriving (Read, Show, Eq)
usage :: IO a usage :: IO a
@ -45,6 +46,7 @@ processCmdLine = go =<< getArgs
Just cmdline -> return $ Continue cmdline Just cmdline -> return $ Continue cmdline
Nothing -> errorMessage "--continue serialization failure" Nothing -> errorMessage "--continue serialization failure"
go ("--simplesh":f:[]) = return $ SimpleSh f go ("--simplesh":f:[]) = return $ SimpleSh f
go ("--chain":h:[]) = return $ Chain h
go (h:[]) = return $ Run h go (h:[]) = return $ Run h
go [] = do go [] = do
s <- takeWhile (/= '\n') <$> readProcess "hostname" ["-f"] s <- takeWhile (/= '\n') <$> readProcess "hostname" ["-f"]
@ -60,6 +62,7 @@ defaultMain getprops = go True =<< processCmdLine
go _ (Set host field) = setPrivData host field go _ (Set host field) = setPrivData host field
go _ (AddKey keyid) = addKey keyid go _ (AddKey keyid) = addKey keyid
go _ (SimpleSh f) = simpleSh f go _ (SimpleSh f) = simpleSh f
go _ (Chain host) = withprops host $ print <=< ensureProperties'
go True cmdline@(Spin _) = buildFirst cmdline $ go False cmdline go True cmdline@(Spin _) = buildFirst cmdline $ go False cmdline
go True cmdline = updateFirst cmdline $ go False cmdline go True cmdline = updateFirst cmdline $ go False cmdline
go False (Spin host) = withprops host $ const $ spin host go False (Spin host) = withprops host $ const $ spin host

View File

@ -4,6 +4,7 @@ module Propellor.Property.Docker where
import Propellor import Propellor
import Propellor.CmdLine import Propellor.CmdLine
import Propellor.SimpleSh
import qualified Propellor.Property.File as File import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt import qualified Propellor.Property.Apt as Apt
import Utility.SafeCommand import Utility.SafeCommand
@ -40,6 +41,8 @@ fromContainerized l = map get l
-- | A docker image, that can be used to run a container. -- | A docker image, that can be used to run a container.
type Image = String type Image = String
-- | A short descriptive name for a container.
-- Should not contain whitespace or other unusual characters.
type ContainerName = String type ContainerName = String
-- | A container is identified by its name, and the host -- | A container is identified by its name, and the host
@ -86,56 +89,83 @@ hasContainer hn cn findcontainer =
warningMessage $ "missing definition for docker container \"" ++ fromContainerId cid warningMessage $ "missing definition for docker container \"" ++ fromContainerId cid
return FailedChange return FailedChange
Just (Container image containerprops) -> Just (Container image containerprops) ->
running image containerprops Property desc (provisionContainer cid)
`requires`
Property desc (ensureContainer cid image containerprops)
where where
cid = ContainerId hn cn cid = ContainerId hn cn
desc = "docker container " ++ fromContainerId cid desc = "docker container " ++ fromContainerId cid
-- Start the container, if it's not already running. ensureContainer :: ContainerId -> Image -> [Containerized Property] -> IO Result
running image containerprops = Property desc $ do ensureContainer cid image containerprops = do
let runps = getRunParams $ containerprops ++ l <- listRunningContainers
-- expose propellor directory inside the container if cid `elem` l
[ volume (localdir++":"++localdir) then do
-- name the container in a predictable way so we runningident <- getrunningident
-- and the user can easily find it later if runningident == Just ident
, name (fromContainerId cid) then return NoChange
-- cd to propellor directory else do
, workdir localdir void $ stopContainer cid
] oldimage <- fromMaybe image <$> commitContainer cid
let ident = ContainerIdent image cid runps removeContainer cid
let runit img = ifM (runContainer cid img runps ident) go oldimage
( do else do
r <- runinside removeContainer cid
return $ MadeChange <> r go image
, return FailedChange where
) ident = ContainerIdent image cid runps
l <- listRunningContainers
if cid `elem` l
then do
runningident <- readish <$> readContainerCommand cid "cat" ["/.propeller-ident"]
if runningident == Just ident
then runinside
else do
void $ stopContainer cid
oldimage <- fromMaybe image <$> commitContainer cid
removeContainer cid
runit oldimage
else do
removeContainer cid
runit image
-- Use propellor binary exposed inside the container -- Start the simplesh server that will be used by propellor
-- (assumes libc compatablity), and run it, passing it the -- to run commands in the container. An interactive shell
-- container@hostname so it knows what to do. -- is also started, so the user can attach and use it if desired.
-- Read its Result code and propigate startsimplesh = "sh -c './propellor --simplesh " ++ namedPipe cid ++ " & ; bash -l'"
runinside :: IO Result
runinside = fromMaybe FailedChange . readish getrunningident = simpleShClient (namedPipe cid) "cat" [propellorIdent] $
<$> readContainerCommand cid "./propellor" [show params] pure . headMaybe . catMaybes . map readish . catMaybes . map getStdout
where setrunningident = simpleShClient (namedPipe cid) "sh"
-- Using Continue avoids auto-update of the binary inside ["-c", "echo '" ++ show ident ++ "' > " ++ propellorIdent]
-- the container. (const noop)
params = Continue $ Run $ fromContainerId cid
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
]
go img = ifM (runContainer img (runps ++ ["-d", "-t"]) startsimplesh)
( do
setrunningident
return MadeChange
, return FailedChange
)
provisionContainer :: ContainerId -> IO Result
provisionContainer cid = do
simpleShClient (namedPipe cid) "./propellor" [show params] (go Nothing)
where
params = Chain $ fromContainerId cid
go lastline (v:rest) = case v of
StdoutLine s -> do
maybe noop putStrLn lastline
hFlush stdout
go (Just s) rest
StderrLine s -> do
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
-- | Two containers with the same ContainerIdent were started from -- | Two containers with the same ContainerIdent were started from
-- the same base image (possibly a different version though), and -- the same base image (possibly a different version though), and
@ -144,10 +174,14 @@ data ContainerIdent = ContainerIdent Image ContainerId [RunParam]
deriving (Read, Show, Eq) deriving (Read, Show, Eq)
-- | The ContainerIdent of a container is written to -- | The ContainerIdent of a container is written to
-- /.propeller-ident inside it. This can be checked to see if -- /.propellor-ident inside it. This can be checked to see if
-- the container has the same ident later. -- the container has the same ident later.
propellerIdent :: FilePath propellorIdent :: FilePath
propellerIdent = "/.propeller-ident" propellorIdent = "/.propellor-ident"
-- | Named pipe used for communication with the container.
namedPipe :: ContainerId -> FilePath
namedPipe cid = "docker/" ++ fromContainerId cid
stopContainer :: ContainerId -> IO Bool stopContainer :: ContainerId -> IO Bool
stopContainer cid = boolSystem dockercmd [Param "stop", Param $ fromContainerId cid ] stopContainer cid = boolSystem dockercmd [Param "stop", Param $ fromContainerId cid ]
@ -156,32 +190,20 @@ removeContainer :: ContainerId -> IO ()
removeContainer cid = void $ boolSystem "sh" removeContainer cid = void $ boolSystem "sh"
[Param "-c", Param $ dockercmd ++ " rm " ++ fromContainerId cid ] [Param "-c", Param $ dockercmd ++ " rm " ++ fromContainerId cid ]
runContainer :: ContainerId -> Image -> [RunParam] -> ContainerIdent -> IO Bool runContainer :: Image -> [RunParam] -> String -> IO Bool
runContainer cid image ps ident = do runContainer image ps cmd = boolSystem dockercmd $ map Param $
ok <- boolSystem dockercmd undefined "run" : (ps ++ [image, cmd])
when ok $
void $ readContainerCommand cid "sh"
["-c", "echo '" ++ show ident ++ "' > " ++ propellerIdent]
return ok
-- | Runs a command inside the container.
readContainerCommand :: ContainerId -> String -> [String] -> IO String
readContainerCommand cid command params = undefined
commitContainer :: ContainerId -> IO (Maybe Image) commitContainer :: ContainerId -> IO (Maybe Image)
commitContainer cid = catchMaybeIO $ commitContainer cid = catchMaybeIO $
readProcess dockercmd ["commit", fromContainerId cid] takeWhile (/= '\n')
<$> readProcess dockercmd ["commit", fromContainerId cid]
-- | Only lists propellor managed containers. -- | Only lists propellor managed containers.
listRunningContainers :: IO [ContainerId] listRunningContainers :: IO [ContainerId]
listRunningContainers = undefined -- docker.io ps listRunningContainers =
catMaybes . map readish . catMaybes . map (lastMaybe . words) . lines
-- | Only lists propellor managed containers. <$> readProcess dockercmd ["ps", "--no-trunc"]
listContainers :: IO [ContainerId]
listContainers = undefined
listImages :: IO [ContainerId]
listImages = undefined -- docker.io images --no-trunc
runProp :: String -> RunParam -> Containerized Property runProp :: String -> RunParam -> Containerized Property
runProp field val = Containerized [param] (Property param (return NoChange)) runProp field val = Containerized [param] (Property param (return NoChange))

View File

@ -22,6 +22,7 @@ data Resp = StdoutLine String | StderrLine String | Done ExitCode
simpleSh :: FilePath -> IO () simpleSh :: FilePath -> IO ()
simpleSh namedpipe = do simpleSh namedpipe = do
nukeFile namedpipe nukeFile namedpipe
createDirectoryIfMissing True (takeDirectory namedpipe)
s <- socket AF_UNIX Stream defaultProtocol s <- socket AF_UNIX Stream defaultProtocol
bind s (SockAddrUnix namedpipe) bind s (SockAddrUnix namedpipe)
listen s 2 listen s 2
@ -71,3 +72,7 @@ simpleShClient namedpipe cmd params handler = do
hPutStrLn h $ show $ Cmd cmd params hPutStrLn h $ show $ Cmd cmd params
resps <- catMaybes . map readish . lines <$> hGetContents h resps <- catMaybes . map readish . lines <$> hGetContents h
hClose h `after` handler resps hClose h `after` handler resps
getStdout :: Resp -> Maybe String
getStdout (StdoutLine s) = Just s
getStdout _ = Nothing