propellor/src/Propellor/Property/Docker.hs

699 lines
23 KiB
Haskell
Raw Normal View History

{-# LANGUAGE FlexibleContexts, TypeSynonymInstances, FlexibleInstances #-}
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.
2014-06-01 01:36:09 +00:00
module Propellor.Property.Docker (
2014-06-01 01:44:50 +00:00
-- * Host properties
2014-06-01 01:36:09 +00:00
installed,
2014-06-01 01:44:50 +00:00
configured,
2014-06-01 01:36:09 +00:00
container,
docked,
imageBuilt,
imagePulled,
2014-06-01 17:35:21 +00:00
memoryLimited,
2014-06-01 01:36:09 +00:00
garbageCollected,
2014-09-19 03:50:13 +00:00
tweaked,
Image(..),
latestImage,
2014-06-01 01:44:50 +00:00
ContainerName,
Container,
HasImage(..),
2014-06-01 01:36:09 +00:00
-- * Container configuration
dns,
hostname,
Publishable,
2014-06-01 01:36:09 +00:00
publish,
expose,
user,
Mountable,
2014-06-01 01:36:09 +00:00
volume,
volumes_from,
workdir,
memory,
2014-06-01 17:35:21 +00:00
cpuShares,
2014-06-01 01:36:09 +00:00
link,
environment,
2014-06-01 01:44:50 +00:00
ContainerAlias,
restartAlways,
restartOnFailure,
restartNever,
2014-06-01 01:36:09 +00:00
-- * Internal use
init,
2014-06-01 01:36:09 +00:00
chain,
) where
2014-03-31 01:01:18 +00:00
import Propellor hiding (init)
2014-11-21 22:55:33 +00:00
import Propellor.Types.Docker
import Propellor.Types.Container
import Propellor.Types.CmdLine
2014-03-31 03:37:54 +00:00
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Cmd as Cmd
2014-11-20 19:15:28 +00:00
import qualified Propellor.Shim as Shim
import Utility.Path
2014-11-19 05:02:13 +00:00
import Utility.ThreadScheduler
2014-06-01 01:36:09 +00:00
import Control.Concurrent.Async hiding (link)
2014-04-02 00:23:11 +00:00
import System.Posix.Directory
import System.Posix.Process
import Prelude hiding (init)
import Data.List hiding (init)
import Data.List.Utils
import qualified Data.Map as M
installed :: Property NoInfo
2014-06-01 01:44:50 +00:00
installed = Apt.installed ["docker.io"]
2014-03-31 03:59:07 +00:00
-- | Configures docker with an authentication file, so that images can be
2014-06-01 01:44:50 +00:00
-- pushed to index.docker.io. Optional.
configured :: Property HasInfo
2014-07-06 19:56:56 +00:00
configured = prop `requires` installed
2014-03-31 01:03:42 +00:00
where
prop = withPrivData src anyContext $ \getcfg ->
2014-07-06 19:56:56 +00:00
property "docker configured" $ getcfg $ \cfg -> ensureProperty $
"/root/.dockercfg" `File.hasContent` (lines cfg)
src = PrivDataSourceFileFromCommand DockerAuthentication
"/root/.dockercfg" "docker login"
2014-04-11 03:20:12 +00:00
-- | A short descriptive name for a container.
-- Should not contain whitespace or other unusual characters,
-- only [a-zA-Z0-9_-] are allowed
type ContainerName = String
-- | A docker container.
data Container = Container Image Host
class HasImage a where
getImageName :: a -> Image
instance HasImage Image where
getImageName = id
instance HasImage Container where
getImageName (Container i _) = i
instance PropAccum Container where
(Container i h) & p = Container i (h & p)
(Container i h) &^ p = Container i (h &^ p)
getProperties (Container _ h) = hostProperties h
-- | Defines a Container with a given name, image, and properties.
-- Properties can be added to configure the Container.
2014-04-11 03:20:12 +00:00
--
-- > container "web-server" "debian"
-- > & publish "80:80"
-- > & Apt.installed {"apache2"]
-- > & ...
container :: ContainerName -> Image -> Container
container cn image = Container image (Host cn [] info)
2014-04-11 03:20:12 +00:00
where
info = dockerInfo mempty
2014-04-11 03:20:12 +00:00
-- | Ensures that a docker container is set up and running.
2014-06-01 01:44:50 +00:00
--
-- The container has its own Properties which are handled by running
-- propellor inside the container.
2014-05-31 20:48:14 +00:00
--
-- When the container's Properties include DNS info, such as a CNAME,
-- that is propigated to the Info of the Host it's docked in.
2014-04-02 16:13:39 +00:00
--
-- Reverting this property ensures that the container is stopped and
-- removed.
docked :: Container -> RevertableProperty
docked ctr@(Container _ h) =
(propigateContainerInfo ctr (go "docked" setup))
<!>
2014-05-31 20:48:14 +00:00
(go "undocked" teardown)
2014-04-10 21:46:03 +00:00
where
cn = hostName h
go desc a = property (desc ++ " " ++ cn) $ do
2014-06-01 00:48:23 +00:00
hn <- asks hostName
let cid = ContainerId hn cn
ensureProperties [a cid (mkContainerInfo cid ctr)]
2014-04-10 21:46:03 +00:00
setup cid (ContainerInfo image runparams) =
2014-04-10 21:46:03 +00:00
provisionContainer cid
`requires`
2014-04-11 03:20:12 +00:00
runningContainer cid image runparams
2014-04-10 21:46:03 +00:00
`requires`
installed
teardown cid (ContainerInfo image _runparams) =
2014-04-10 21:46:03 +00:00
combineProperties ("undocked " ++ fromContainerId cid)
[ stoppedContainer cid
, property ("cleaned up " ++ fromContainerId cid) $
liftIO $ report <$> mapM id
2014-04-03 00:56:02 +00:00
[ removeContainer cid
, removeImage image
]
]
2014-04-02 04:52:39 +00:00
-- | Build the image from a directory containing a Dockerfile.
imageBuilt :: HasImage c => FilePath -> c -> Property NoInfo
imageBuilt directory ctr = describe built msg
where
msg = "docker image " ++ (imageIdentifier image) ++ " built from " ++ directory
built = Cmd.cmdProperty' dockercmd ["build", "--tag", imageIdentifier image, "./"] workDir
workDir p = p { cwd = Just directory }
image = getImageName ctr
-- | Pull the image from the standard Docker Hub registry.
imagePulled :: HasImage c => c -> Property NoInfo
imagePulled ctr = describe pulled msg
where
msg = "docker image " ++ (imageIdentifier image) ++ " pulled"
pulled = Cmd.cmdProperty dockercmd ["pull", imageIdentifier image]
image = getImageName ctr
propigateContainerInfo :: (IsProp (Property i)) => Container -> Property i -> Property HasInfo
propigateContainerInfo ctr@(Container _ h) p = propigateContainer ctr p'
where
p' = infoProperty
(propertyDesc p)
(propertySatisfy p)
(propertyInfo p <> dockerinfo)
(propertyChildren p)
dockerinfo = dockerInfo $
mempty { _dockerContainers = M.singleton (hostName h) h }
2014-05-31 20:48:14 +00:00
mkContainerInfo :: ContainerId -> Container -> ContainerInfo
mkContainerInfo cid@(ContainerId hn _cn) (Container img h) =
ContainerInfo img runparams
2014-04-11 03:20:12 +00:00
where
runparams = map (\(DockerRunParam mkparam) -> mkparam hn)
(_dockerRunParams info)
2014-06-09 05:45:58 +00:00
info = _dockerinfo $ hostInfo h'
h' = h
-- Restart by default so container comes up on
-- boot or when docker is upgraded.
&^ restartAlways
-- Expose propellor directory inside the container.
2014-04-11 03:20:12 +00:00
& volume (localdir++":"++localdir)
-- Name the container in a predictable way so we
-- and the user can easily find it later. This property
-- comes last, so it cannot be overridden.
2014-04-11 03:20:12 +00:00
& name (fromContainerId cid)
2014-04-02 03:24:31 +00:00
-- | Causes *any* docker images that are not in use by running containers to
-- be deleted. And deletes any containers that propellor has set up
-- before that are not currently running. Does not delete any containers
-- that were not set up using propellor.
--
-- Generally, should come after the properties for the desired containers.
garbageCollected :: Property NoInfo
2014-04-02 03:24:31 +00:00
garbageCollected = propertyList "docker garbage collected"
[ gccontainers
, gcimages
]
where
gccontainers = property "docker containers garbage collected" $
liftIO $ report <$> (mapM removeContainer =<< listContainers AllContainers)
gcimages = property "docker images garbage collected" $ do
liftIO $ report <$> (mapM removeImage =<< listImages)
2014-04-02 03:24:31 +00:00
2014-09-19 03:50:13 +00:00
-- | Tweaks a container to work well with docker.
--
-- Currently, this consists of making pam_loginuid lines optional in
2014-12-09 18:22:37 +00:00
-- the pam config, to work around <https://github.com/docker/docker/issues/5663>
2014-09-19 03:50:13 +00:00
-- which affects docker 1.2.0.
tweaked :: Property NoInfo
2014-09-19 03:50:13 +00:00
tweaked = trivial $
cmdProperty "sh" ["-c", "sed -ri 's/^session\\s+required\\s+pam_loginuid.so$/session optional pam_loginuid.so/' /etc/pam.d/*"]
`describe` "tweaked for docker"
2014-06-01 17:35:21 +00:00
-- | Configures the kernel to respect docker memory limits.
--
-- This assumes the system boots using grub 2. And that you don't need any
-- other GRUB_CMDLINE_LINUX_DEFAULT settings.
--
-- Only takes effect after reboot. (Not automated.)
memoryLimited :: Property NoInfo
2014-06-01 17:35:21 +00:00
memoryLimited = "/etc/default/grub" `File.containsLine` cfg
`describe` "docker memory limited"
`onChange` cmdProperty "update-grub" []
where
cmdline = "cgroup_enable=memory swapaccount=1"
cfg = "GRUB_CMDLINE_LINUX_DEFAULT=\""++cmdline++"\""
data ContainerInfo = ContainerInfo Image [RunParam]
2014-04-02 01:53:11 +00:00
-- | Parameters to pass to `docker run` when creating a container.
type RunParam = String
-- | ImageID is an image identifier to perform action on images. An
-- ImageID can be the name of an container image, a UID, etc.
--
-- It just encapsulates a String to avoid the definition of a String
-- instance of ImageIdentifier.
newtype ImageID = ImageID String
-- | Used to perform Docker action on an image.
--
-- Minimal complete definition: `imageIdentifier`
class ImageIdentifier i where
-- | For internal purposes only.
toImageID :: i -> ImageID
toImageID = ImageID . imageIdentifier
-- | A string that Docker can use as an image identifier.
imageIdentifier :: i -> String
instance ImageIdentifier ImageID where
imageIdentifier (ImageID i) = i
toImageID = id
-- | A docker image, that can be used to run a container. The user has
-- to specify a name and can provide an optional tag.
-- See <http://docs.docker.com/userguide/dockerimages/ Docker Image Documention>
-- for more information.
data Image = Image
{ repository :: String
, tag :: Maybe String
}
deriving (Eq, Read, Show)
-- | Defines a Docker image without any tag. This is considered by
-- Docker as the latest image of the provided repository.
latestImage :: String -> Image
latestImage repo = Image repo Nothing
instance ImageIdentifier Image where
-- | The format of the imageIdentifier of an `Image` is:
-- repository | repository:tag
imageIdentifier i = repository i ++ (maybe "" ((++) ":") $ tag i)
-- | The UID of an image. This UID is generated by Docker.
newtype ImageUID = ImageUID String
instance ImageIdentifier ImageUID where
imageIdentifier (ImageUID uid) = uid
2014-04-02 01:53:11 +00:00
-- | Set custom dns server for container.
dns :: String -> Property HasInfo
2014-04-02 01:53:11 +00:00
dns = runProp "dns"
-- | Set container host name.
hostname :: String -> Property HasInfo
2014-04-02 01:53:11 +00:00
hostname = runProp "hostname"
-- | Set name of container.
name :: String -> Property HasInfo
2014-04-02 01:53:11 +00:00
name = runProp "name"
class Publishable p where
toPublish :: p -> String
instance Publishable (Bound Port) where
toPublish p = show (hostSide p) ++ ":" ++ show (containerSide p)
-- | string format: ip:hostPort:containerPort | ip::containerPort | hostPort:containerPort
instance Publishable String where
toPublish = id
2014-04-02 01:53:11 +00:00
-- | Publish a container's port to the host
publish :: Publishable p => p -> Property HasInfo
publish = runProp "publish" . toPublish
2014-04-02 01:53:11 +00:00
2014-05-19 21:27:21 +00:00
-- | Expose a container's port without publishing it.
expose :: String -> Property HasInfo
2014-05-19 21:27:21 +00:00
expose = runProp "expose"
2014-04-02 01:53:11 +00:00
-- | Username or UID for container.
user :: String -> Property HasInfo
2014-04-02 01:53:11 +00:00
user = runProp "user"
class Mountable p where
toMount :: p -> String
instance Mountable (Bound FilePath) where
toMount p = hostSide p ++ ":" ++ containerSide p
-- | string format: [host-dir]:[container-dir]:[rw|ro]
--
2014-04-08 05:21:23 +00:00
-- With just a directory, creates a volume in the container.
instance Mountable String where
toMount = id
-- | Mount a volume
volume :: Mountable v => v -> Property HasInfo
volume = runProp "volume" . toMount
2014-04-02 01:53:11 +00:00
2014-04-08 05:21:23 +00:00
-- | Mount a volume from the specified container into the current
-- container.
volumes_from :: ContainerName -> Property HasInfo
2014-04-08 05:45:19 +00:00
volumes_from cn = genProp "volumes-from" $ \hn ->
2014-04-08 05:21:23 +00:00
fromContainerId (ContainerId hn cn)
2014-04-02 01:53:11 +00:00
-- | Work dir inside the container.
workdir :: String -> Property HasInfo
2014-04-02 01:53:11 +00:00
workdir = runProp "workdir"
-- | Memory limit for container.
2014-06-01 17:35:21 +00:00
-- Format: <number><optional unit>, where unit = b, k, m or g
--
-- Note: Only takes effect when the host has the memoryLimited property
-- enabled.
memory :: String -> Property HasInfo
2014-04-02 01:53:11 +00:00
memory = runProp "memory"
2014-06-01 17:35:21 +00:00
-- | CPU shares (relative weight).
2014-06-01 17:40:06 +00:00
--
-- By default, all containers run at the same priority, but you can tell
-- the kernel to give more CPU time to a container using this property.
cpuShares :: Int -> Property HasInfo
2014-06-01 17:35:21 +00:00
cpuShares = runProp "cpu-shares" . show
2014-04-08 05:10:54 +00:00
-- | Link with another container on the same host.
link :: ContainerName -> ContainerAlias -> Property HasInfo
2014-04-19 05:28:46 +00:00
link linkwith calias = genProp "link" $ \hn ->
fromContainerId (ContainerId hn linkwith) ++ ":" ++ calias
2014-04-08 05:10:54 +00:00
-- | A short alias for a linked container.
-- Each container has its own alias namespace.
type ContainerAlias = String
-- | This property is enabled by default for docker containers configured by
-- propellor; as well as keeping badly behaved containers running,
-- it ensures that containers get started back up after reboot or
-- after docker is upgraded.
restartAlways :: Property HasInfo
restartAlways = runProp "restart" "always"
-- | Docker will restart the container if it exits nonzero.
-- If a number is provided, it will be restarted only up to that many
-- times.
restartOnFailure :: Maybe Int -> Property HasInfo
restartOnFailure Nothing = runProp "restart" "on-failure"
restartOnFailure (Just n) = runProp "restart" ("on-failure:" ++ show n)
-- | Makes docker not restart a container when it exits
-- Note that this includes not restarting it on boot!
restartNever :: Property HasInfo
restartNever = runProp "restart" "no"
-- | Set environment variable with a tuple composed by the environment
-- variable name and its value.
environment :: (String, String) -> Property HasInfo
environment (k, v) = runProp "env" $ k ++ "=" ++ v
-- | A container is identified by its name, and the host
-- on which it's deployed.
data ContainerId = ContainerId
{ containerHostName :: HostName
, containerName :: ContainerName
}
deriving (Eq, Read, Show)
2014-04-02 01:53:11 +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)
toContainerId :: String -> Maybe ContainerId
toContainerId s
| myContainerSuffix `isSuffixOf` s = case separate (== '.') (desuffix s) of
(cn, hn)
| null hn || null cn -> Nothing
| otherwise -> Just $ ContainerId hn cn
| otherwise = Nothing
where
desuffix = reverse . drop len . reverse
len = length myContainerSuffix
fromContainerId :: ContainerId -> String
fromContainerId (ContainerId hn cn) = cn++"."++hn++myContainerSuffix
myContainerSuffix :: String
myContainerSuffix = ".propellor"
containerDesc :: (IsProp (Property i)) => ContainerId -> Property i -> Property i
containerDesc cid p = p `describe` desc
where
2014-11-19 05:40:56 +00:00
desc = "container " ++ fromContainerId cid ++ " " ++ propertyDesc p
runningContainer :: ContainerId -> Image -> [RunParam] -> Property NoInfo
runningContainer cid@(ContainerId hn cn) image runps = containerDesc cid $ property "running" $ do
l <- liftIO $ listContainers RunningContainers
if cid `elem` l
2014-11-19 05:02:13 +00:00
then checkident =<< liftIO getrunningident
else ifM (liftIO $ elem cid <$> listContainers AllContainers)
( do
-- The container exists, but is not
-- running. Its parameters may have
-- changed, but we cannot tell without
-- starting it up first.
void $ liftIO $ startContainer cid
2014-10-10 17:51:52 +00:00
-- It can take a while for the container to
2014-11-19 05:02:13 +00:00
-- start up enough for its ident file to be
-- written, so retry for up to 60 seconds.
checkident =<< liftIO (retry 60 $ getrunningident)
2014-04-04 19:47:06 +00:00
, go image
)
where
2014-04-01 17:04:24 +00:00
ident = ContainerIdent image hn cn runps
-- Check if the ident has changed; if so the
-- parameters of the container differ and it must
-- be restarted.
checkident (Right runningident)
2014-10-10 17:51:52 +00:00
| runningident == Just ident = noChange
| otherwise = do
void $ liftIO $ stopContainer cid
restartcontainer
checkident (Left errmsg) = do
warningMessage errmsg
return FailedChange
2014-04-04 19:47:06 +00:00
restartcontainer = do
oldimage <- liftIO $
fromMaybe (toImageID image) . fmap toImageID <$>
commitContainer cid
void $ liftIO $ removeContainer cid
2014-04-04 19:47:06 +00:00
go oldimage
getrunningident = withTmpFile "dockerrunsane" $ \t h -> do
-- detect #774376 which caused docker exec to not enter
-- the container namespace, and be able to access files
-- outside
hClose h
void . checkSuccessProcess . processHandle =<<
createProcess (inContainerProcess cid []
["rm", "-f", t])
ifM (doesFileExist t)
( Right . readish <$>
readProcess' (inContainerProcess cid []
["cat", propellorIdent])
, return $ Left "docker exec failed to enter chroot properly (maybe an old kernel version?)"
)
2014-04-04 19:03:03 +00:00
retry :: Int -> IO (Either e (Maybe a)) -> IO (Either e (Maybe a))
retry 0 _ = return (Right Nothing)
2014-11-19 05:02:13 +00:00
retry n a = do
v <- a
case v of
Right Nothing -> do
threadDelaySeconds (Seconds 1)
2014-11-19 05:02:13 +00:00
retry (n-1) a
_ -> return v
go img = liftIO $ do
clearProvisionedFlag cid
createDirectoryIfMissing True (takeDirectory $ identFile cid)
shim <- Shim.setup (localdir </> "propellor") Nothing (localdir </> shimdir cid)
writeFile (identFile cid) (show ident)
toResult <$> runContainer img
(runps ++ ["-i", "-d", "-t"])
[shim, "--continue", show (DockerInit (fromContainerId cid))]
-- | Called when propellor is running inside a docker container.
-- The string should be the container's ContainerId.
--
-- This process is effectively init inside the container.
-- It even needs to wait on zombie processes!
--
-- In the foreground, run an interactive bash (or sh) shell,
-- so that the user can interact with it when attached to the container.
2014-04-02 01:53:11 +00:00
--
-- When the system reboots, docker restarts the container, and this is run
-- again. So, to make the necessary services get started on boot, this needs
-- to provision the container then. However, if the container is already
-- being provisioned by the calling propellor, it would be redundant and
-- problimatic to also provisoon it here, when not booting up.
2014-04-02 01:53:11 +00:00
--
-- The solution is a flag file. If the flag file exists, then the container
-- was already provisioned. So, it must be a reboot, and time to provision
-- again. If the flag file doesn't exist, don't provision here.
init :: String -> IO ()
init s = case toContainerId s of
Nothing -> error $ "Invalid ContainerId: " ++ s
Just cid -> do
2014-04-02 00:23:11 +00:00
changeWorkingDirectory localdir
writeFile propellorIdent . show =<< readIdentFile cid
2014-04-04 01:22:37 +00:00
whenM (checkProvisionedFlag cid) $ do
2014-04-04 03:30:23 +00:00
let shim = Shim.file (localdir </> "propellor") (localdir </> shimdir cid)
unlessM (boolSystem shim [Param "--continue", Param $ show $ toChain cid]) $
2014-04-02 01:53:11 +00:00
warningMessage "Boot provision failed!"
2014-04-04 22:46:54 +00:00
void $ async $ job reapzombies
job $ do
2014-04-04 22:50:54 +00:00
void $ tryIO $ ifM (inPath "bash")
( boolSystem "bash" [Param "-l"]
, boolSystem "/bin/sh" []
)
putStrLn "Container is still running. Press ^P^Q to detach."
where
2014-04-04 22:46:54 +00:00
job = forever . void . tryIO
reapzombies = void $ getAnyProcessStatus True False
-- | Once a container is running, propellor can be run inside
-- it to provision it.
provisionContainer :: ContainerId -> Property NoInfo
2014-07-06 21:58:27 +00:00
provisionContainer cid = containerDesc cid $ property "provisioned" $ liftIO $ do
2014-04-04 03:30:23 +00:00
let shim = Shim.file (localdir </> "propellor") (localdir </> shimdir cid)
let params = ["--continue", show $ toChain cid]
msgh <- mkMessageHandle
2014-11-19 05:02:13 +00:00
let p = inContainerProcess cid
(if isConsole msgh then ["-it"] else [])
2014-11-19 04:30:06 +00:00
(shim : params)
2014-11-19 05:02:13 +00:00
r <- withHandle StdoutHandle createProcessSuccess p $
2014-11-20 19:15:28 +00:00
processChainOutput
2014-04-02 01:53:11 +00:00
when (r /= FailedChange) $
setProvisionedFlag cid
return r
toChain :: ContainerId -> CmdLine
toChain cid = DockerChain (containerHostName cid) (fromContainerId cid)
chain :: [Host] -> HostName -> String -> IO ()
chain hostlist hn s = case toContainerId s of
Nothing -> errorMessage "bad container id"
Just cid -> case findHostNoAlias hostlist hn of
Nothing -> errorMessage ("cannot find host " ++ hn)
Just parenthost -> case M.lookup (containerName cid) (_dockerContainers $ _dockerinfo $ hostInfo parenthost) of
Nothing -> errorMessage ("cannot find container " ++ containerName cid ++ " docked on host " ++ hn)
Just h -> go cid h
where
go cid h = do
2014-11-19 05:32:09 +00:00
changeWorkingDirectory localdir
onlyProcess (provisioningLock cid) $ do
r <- runPropellor h $ ensureProperties $
map ignoreInfo $
hostProperties h
2014-11-19 05:32:09 +00:00
putStrLn $ "\n" ++ show r
stopContainer :: ContainerId -> IO Bool
stopContainer cid = boolSystem dockercmd [Param "stop", Param $ fromContainerId cid ]
startContainer :: ContainerId -> IO Bool
startContainer cid = boolSystem dockercmd [Param "start", Param $ fromContainerId cid ]
stoppedContainer :: ContainerId -> Property NoInfo
stoppedContainer cid = containerDesc cid $ property desc $
ifM (liftIO $ elem cid <$> listContainers RunningContainers)
( liftIO cleanup `after` ensureProperty
(property desc $ liftIO $ toResult <$> stopContainer cid)
2014-04-03 00:56:02 +00:00
, return NoChange
)
where
desc = "stopped"
2014-04-04 01:22:37 +00:00
cleanup = do
nukeFile $ identFile cid
removeDirectoryRecursive $ shimdir cid
clearProvisionedFlag cid
2014-04-02 17:56:16 +00:00
2014-04-02 03:24:31 +00:00
removeContainer :: ContainerId -> IO Bool
removeContainer cid = catchBoolIO $
snd <$> processTranscript dockercmd ["rm", fromContainerId cid ] Nothing
removeImage :: ImageIdentifier i => i -> IO Bool
2014-04-02 03:24:31 +00:00
removeImage image = catchBoolIO $
snd <$> processTranscript dockercmd ["rmi", imageIdentifier image] Nothing
runContainer :: ImageIdentifier i => i -> [RunParam] -> [String] -> IO Bool
runContainer image ps cmd = boolSystem dockercmd $ map Param $
"run" : (ps ++ (imageIdentifier image) : cmd)
2014-11-19 05:02:13 +00:00
inContainerProcess :: ContainerId -> [String] -> [String] -> CreateProcess
inContainerProcess cid ps cmd = proc dockercmd ("exec" : ps ++ [fromContainerId cid] ++ cmd)
2014-11-19 04:30:06 +00:00
commitContainer :: ContainerId -> IO (Maybe ImageUID)
commitContainer cid = catchMaybeIO $
ImageUID . takeWhile (/= '\n')
<$> readProcess dockercmd ["commit", fromContainerId cid]
2014-04-01 17:04:24 +00:00
data ContainerFilter = RunningContainers | AllContainers
2014-04-01 16:37:57 +00:00
deriving (Eq)
-- | 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 =
catMaybes . map toContainerId . concat . map (split ",")
. 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"]
listImages :: IO [ImageUID]
listImages = map ImageUID . lines <$> readProcess dockercmd ["images", "--all", "--quiet"]
2014-04-02 03:24:31 +00:00
runProp :: String -> RunParam -> Property HasInfo
2014-06-09 05:45:58 +00:00
runProp field val = pureInfoProperty (param) $ dockerInfo $
mempty { _dockerRunParams = [DockerRunParam (\_ -> "--"++param)] }
where
param = field++"="++val
genProp :: String -> (HostName -> RunParam) -> Property HasInfo
2014-06-09 05:45:58 +00:00
genProp field mkval = pureInfoProperty field $ dockerInfo $
mempty { _dockerRunParams = [DockerRunParam (\hn -> "--"++field++"=" ++ mkval hn)] }
2014-04-08 05:10:54 +00:00
2014-11-21 22:55:33 +00:00
dockerInfo :: DockerInfo Host -> Info
2014-06-09 05:45:58 +00:00
dockerInfo i = mempty { _dockerinfo = i }
2014-06-01 02:00:11 +00:00
2014-04-02 01:53:11 +00:00
-- | The ContainerIdent of a container is written to
2014-12-09 18:22:37 +00:00
-- </.propellor-ident> inside it. This can be checked to see if
2014-04-02 01:53:11 +00:00
-- the container has the same ident later.
propellorIdent :: FilePath
propellorIdent = "/.propellor-ident"
2014-04-02 01:53:11 +00:00
provisionedFlag :: ContainerId -> FilePath
2014-04-04 01:22:37 +00:00
provisionedFlag cid = "docker" </> fromContainerId cid ++ ".provisioned"
2014-04-02 01:53:11 +00:00
clearProvisionedFlag :: ContainerId -> IO ()
clearProvisionedFlag = nukeFile . provisionedFlag
2014-04-02 01:53:11 +00:00
setProvisionedFlag :: ContainerId -> IO ()
setProvisionedFlag cid = do
createDirectoryIfMissing True (takeDirectory (provisionedFlag cid))
writeFile (provisionedFlag cid) "1"
2014-04-02 01:53:11 +00:00
checkProvisionedFlag :: ContainerId -> IO Bool
checkProvisionedFlag = doesFileExist . provisionedFlag
provisioningLock :: ContainerId -> FilePath
provisioningLock cid = "docker" </> fromContainerId cid ++ ".lock"
2014-04-04 01:22:37 +00:00
shimdir :: ContainerId -> FilePath
shimdir cid = "docker" </> fromContainerId cid ++ ".shim"
2014-04-02 01:53:11 +00:00
identFile :: ContainerId -> FilePath
2014-04-04 01:22:37 +00:00
identFile cid = "docker" </> fromContainerId cid ++ ".ident"
2014-04-02 01:53:11 +00:00
readIdentFile :: ContainerId -> IO ContainerIdent
readIdentFile cid = fromMaybe (error "bad ident in identFile")
. readish <$> readFile (identFile cid)
2014-04-02 01:53:11 +00:00
dockercmd :: String
dockercmd = "docker"
2014-04-02 04:52:39 +00:00
report :: [Bool] -> Result
report rmed
| or rmed = MadeChange
| otherwise = NoChange