Skip to content

Commit

Permalink
Introduce concurrent run strategy for launching containers
Browse files Browse the repository at this point in the history
  • Loading branch information
alexbiehl committed Jun 17, 2024
1 parent 5a249cf commit 8925211
Show file tree
Hide file tree
Showing 8 changed files with 277 additions and 120 deletions.
1 change: 1 addition & 0 deletions src/TestContainers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module TestContainers
M.setExpose,
M.setWaitingFor,
M.withFollowLogs,
M.withDependencies,

-- * Logs
M.LogConsumer,
Expand Down
8 changes: 5 additions & 3 deletions src/TestContainers/Config.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
module TestContainers.Config
( Config (..),
( RunStrategy (..),
Config (..),
defaultConfig,
defaultDockerConfig,
determineConfig,
)
where

import {-# SOURCE #-} TestContainers.Docker (createRyukReaper)
import TestContainers.Monad (Config (..))
import TestContainers.Monad (Config (..), RunStrategy (..))

-- | Default configuration.
--
Expand All @@ -17,7 +18,8 @@ defaultConfig =
Config
{ configDefaultWaitTimeout = Just 60,
configTracer = mempty,
configCreateReaper = createRyukReaper
configCreateReaper = createRyukReaper,
configRunStrategy = SequentialRunStrategy
}

-- | Default configuration.
Expand Down
181 changes: 124 additions & 57 deletions src/TestContainers/Docker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down Expand Up @@ -94,6 +95,7 @@ module TestContainers.Docker
setLink,
setExpose,
setWaitingFor,
withDependencies,
run,

-- * Following logs
Expand Down Expand Up @@ -158,7 +160,8 @@ module TestContainers.Docker
where

import Control.Concurrent (threadDelay)
import Control.Exception (IOException, throw)
import qualified Control.Concurrent.Async
import Control.Exception (IOException, evaluate, throw)

Check warning on line 164 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / stack / ghc 9.0.2

The import of ‘evaluate’

Check warning on line 164 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

The import of ‘evaluate’

Check warning on line 164 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.8

The import of ‘evaluate’

Check warning on line 164 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.4

The import of ‘evaluate’
import Control.Monad (forM_, replicateM, unless)
import Control.Monad.Catch
( Exception,
Expand All @@ -169,11 +172,12 @@ import Control.Monad.Catch
try,
)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.IO.Unlift (MonadUnliftIO (withRunInIO))
import Control.Monad.IO.Unlift (MonadUnliftIO (withRunInIO), askRunInIO)
import Control.Monad.Reader (MonadReader (..))
import Control.Monad.Trans.Resource
( ReleaseKey,
ResIO,
allocate,
register,
runResourceT,
)
Expand Down Expand Up @@ -209,12 +213,13 @@ import Optics.Optic ((%), (<&>))
import System.Directory (doesFileExist)
import System.Environment (lookupEnv)
import System.IO (Handle, hClose)
import System.IO.Unsafe (unsafePerformIO)
import System.IO.Unsafe (unsafeInterleaveIO, unsafePerformIO)
import qualified System.Process as Process
import qualified System.Random as Random
import System.Timeout (timeout)
import TestContainers.Config
( Config (..),
RunStrategy (..),
defaultDockerConfig,
determineConfig,
)
Expand Down Expand Up @@ -263,6 +268,7 @@ import TestContainers.Docker.State
import TestContainers.Monad
( MonadDocker,
TestContainer,
defer,
)
import TestContainers.Trace (Trace (..), Tracer, newTracer, withTrace)
import Prelude hiding (error, id)
Expand All @@ -288,7 +294,8 @@ data ContainerRequest = ContainerRequest
labels :: [(Text, Text)],
noReaper :: Bool,
followLogs :: Maybe LogConsumer,
workDirectory :: Maybe Text
workDirectory :: Maybe Text,
dependencies :: [Container]
}

instance WithoutReaper ContainerRequest where
Expand Down Expand Up @@ -324,7 +331,8 @@ containerRequest image =
labels = mempty,
noReaper = False,
followLogs = Nothing,
workDirectory = Nothing
workDirectory = Nothing,
dependencies = []
}

-- | Set the name of a Docker container. This is equivalent to invoking @docker run@
Expand Down Expand Up @@ -453,6 +461,13 @@ withFollowLogs :: LogConsumer -> ContainerRequest -> ContainerRequest
withFollowLogs logConsumer request =
request {followLogs = Just logConsumer}

-- |
--
-- @since x.x.x
withDependencies :: [Container] -> ContainerRequest -> ContainerRequest
withDependencies dependencies request =
request {dependencies}

-- | Defintion of a 'Port'. Allows for specifying ports using various protocols. Due to the
-- 'Num' and 'IsString' instance allows for convenient Haskell literals.
--
Expand Down Expand Up @@ -556,7 +571,8 @@ run request = do
labels,
noReaper,
followLogs,
workDirectory
workDirectory,
dependencies
} = request

config@Config {configTracer, configCreateReaper} <-
Expand All @@ -568,8 +584,6 @@ run request = do
pure []
else reaperLabels <$> configCreateReaper

image@Image {tag} <- runToImage toImage

name <-
case naming of
RandomName -> return Nothing
Expand All @@ -578,59 +592,110 @@ run request = do
Just . (prefix <>) . ("-" <>) . pack
<$> replicateM 6 (Random.randomRIO ('a', 'z'))

let dockerRun :: [Text]
dockerRun =
concat $
[["run"]]
++ [["--detach"]]
++ [["--name", containerName] | Just containerName <- [name]]
++ [["--label", label <> "=" <> value] | (label, value) <- additionalLabels ++ labels]
++ [["--env", variable <> "=" <> value] | (variable, value) <- env]
++ [["--publish", pack (show port) <> "/" <> protocol] | Port {port, protocol} <- exposedPorts]
++ [["--network", networkName] | Just (Right networkName) <- [network]]
++ [["--network", networkId dockerNetwork] | Just (Left dockerNetwork) <- [network]]
++ [["--network-alias", alias] | Just alias <- [networkAlias]]
++ [["--link", container] | container <- links]
++ [["--volume", src <> ":" <> dest] | (src, dest) <- volumeMounts]
++ [["--rm"] | rmOnExit]
++ [["--workdir", workdir] | Just workdir <- [workDirectory]]
++ [["--memory", value] | Just value <- [memory]]
++ [["--cpus", value] | Just value <- [cpus]]
++ [[tag]]
++ [command | Just command <- [cmd]]

stdout <- docker configTracer dockerRun

let id :: ContainerId
!id =
-- N.B. Force to not leak STDOUT String
strip (pack stdout)

-- Careful, this is really meant to be lazy
~inspectOutput =
unsafePerformIO $
internalInspect configTracer id
(actuallyRunDocker, waitOnContainer) <- applyRunStrategy $ do
image@Image {tag} <- runToImage toImage

-- We don't issue 'ReleaseKeys' for cleanup anymore. Ryuk takes care of cleanup
-- for us once the session has been closed.
releaseKey <- register (pure ())
liftIO $
forM_ dependencies $
\Container {wait} -> wait

let dockerRun :: [Text]
dockerRun =
concat $
[["run"]]
++ [["--detach"]]
++ [["--name", containerName] | Just containerName <- [name]]
++ [["--label", label <> "=" <> value] | (label, value) <- additionalLabels ++ labels]
++ [["--env", variable <> "=" <> value] | (variable, value) <- env]
++ [["--publish", pack (show port) <> "/" <> protocol] | Port {port, protocol} <- exposedPorts]
++ [["--network", networkName] | Just (Right networkName) <- [network]]
++ [["--network", networkId dockerNetwork] | Just (Left dockerNetwork) <- [network]]
++ [["--network-alias", alias] | Just alias <- [networkAlias]]
++ [["--link", container] | container <- links]
++ [["--volume", src <> ":" <> dest] | (src, dest) <- volumeMounts]
++ [["--rm"] | rmOnExit]
++ [["--workdir", workdir] | Just workdir <- [workDirectory]]
++ [["--memory", value] | Just value <- [memory]]
++ [["--cpus", value] | Just value <- [cpus]]
++ [[tag]]
++ [command | Just command <- [cmd]]

stdout <- docker configTracer dockerRun

let id :: ContainerId
!id =
-- N.B. Force to not leak STDOUT String
strip (pack stdout)

-- Careful, this is really meant to be lazy
~inspectOutput =
unsafePerformIO $
internalInspect configTracer id

-- We don't issue 'ReleaseKeys' for cleanup anymore. Ryuk takes care of cleanup
-- for us once the session has been closed.
releaseKey <- register (pure ())

forM_ followLogs $
dockerFollowLogs configTracer id

let container =
Container
{ id,
releaseKey,
image,
inspectOutput,
config,
wait = pure ()
}

-- Last but not least, execute the WaitUntilReady checks
waitUntilReady container readiness

pure container

-- We want to be very gentle and not force the container if possible so that we can
-- install the wait action.
~container <-
actuallyRunDocker

pure $
let ~Container {..} = container

Check warning on line 663 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / stack / ghc 9.0.2

This binding for ‘config’ shadows the existing binding

Check warning on line 663 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.2.8

This binding for ‘config’ shadows the existing binding

Check warning on line 663 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.4.8

This binding for ‘config’ shadows the existing binding

Check warning on line 663 in src/TestContainers/Docker.hs

View workflow job for this annotation

GitHub Actions / ubuntu-latest / ghc 9.6.4

This binding for ‘config’ shadows the existing binding
in Container
{ wait = waitOnContainer,
..
}

forM_ followLogs $
dockerFollowLogs configTracer id
applyRunStrategy ::
TestContainer a ->
TestContainer (TestContainer a, IO ())
applyRunStrategy action = do
Config {configTracer, configRunStrategy} <-
ask
case configRunStrategy of
SequentialRunStrategy ->
pure (action, pure ())
ConcurrentRunStrategy _limit -> do
runInIO <-
askRunInIO

let container =
Container
{ id,
releaseKey,
image,
inspectOutput,
config
}
(_releaseKey, handle) <-
allocate
(Control.Concurrent.Async.async (runInIO action))
Control.Concurrent.Async.cancel

let returnAction =
liftIO $ unsafeInterleaveIO $ do
Control.Concurrent.Async.wait handle

waitAction = do
withTrace configTracer TraceWaitOnDependency
_ <- Control.Concurrent.Async.wait handle
pure ()

-- Last but not least, execute the WaitUntilReady checks
waitUntilReady container readiness
defer waitAction

pure container
pure (returnAction, waitAction)

-- | Sets up a Ryuk 'Reaper'.
--
Expand Down Expand Up @@ -1109,7 +1174,9 @@ data Container = Container
-- | Configuration used to create and run this container.
config :: Config,
-- | Memoized output of `docker inspect`. This is being calculated lazily.
inspectOutput :: InspectOutput
inspectOutput :: InspectOutput,
-- | Wait on the container as a dependency.
wait :: IO ()
}

-- | Returns the id of the container.
Expand Down
Loading

0 comments on commit 8925211

Please sign in to comment.