Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- ingredient :: Ingredient
- withContainers :: forall a. TestContainer a -> (IO a -> TestTree) -> TestTree
- data State
- data Status
- type ResIO = ResourceT IO
- type ImageTag = Text
- data Image
- data ToImage
- data ContainerRequest
- type LogConsumer = Pipe -> ByteString -> IO ()
- data NetworkRequest
- data Network
- type NetworkId = Text
- data Port = Port {}
- data Container
- type InspectOutput = Value
- data WaitUntilReady
- data Pipe
- type MonadDocker m = m ~ TestContainer
- data TestContainer a
- data Config = Config {}
- data Tracer
- data DockerException
- = DockerException { }
- | InspectUnknownContainerId {
- id :: ContainerId
- | InspectOutputInvalidJSON {
- id :: ContainerId
- | InspectOutputMissingNetwork {
- id :: ContainerId
- | InspectOutputUnexpected {
- id :: ContainerId
- | UnknownPortMapping {
- id :: ContainerId
- port :: Text
- newtype TimeoutException = TimeoutException {
- id :: ContainerId
- newtype UnexpectedEndOfPipe = UnexpectedEndOfPipe {
- id :: ContainerId
- pattern TraceDockerInvocation :: [Text] -> Text -> ExitCode -> Trace
- pattern TraceDockerFollowLogs :: [Text] -> Trace
- pattern TraceDockerStdout :: Text -> Trace
- pattern TraceDockerStderr :: Text -> Trace
- pattern TraceWaitUntilReady :: Maybe Int -> Trace
- pattern TraceOpenSocket :: Text -> Int -> Maybe IOException -> Trace
- pattern TraceHttpCall :: Text -> Int -> Either String Int -> Trace
- stop :: Container -> TestContainer ()
- run :: ContainerRequest -> TestContainer Container
- build :: ToImage -> TestContainer ToImage
- setEnv :: [(Text, Text)] -> ContainerRequest -> ContainerRequest
- (&) :: a -> (a -> b) -> b
- runResourceT :: MonadUnliftIO m => ResourceT m a -> m a
- imageTag :: Image -> ImageTag
- fromTag :: ImageTag -> ToImage
- fromImageId :: Text -> ToImage
- fromBuildContext :: FilePath -> Maybe FilePath -> ToImage
- containerRequest :: ToImage -> ContainerRequest
- withoutReaper :: WithoutReaper request => request -> request
- setName :: Text -> ContainerRequest -> ContainerRequest
- setFixedName :: Text -> ContainerRequest -> ContainerRequest
- setSuffixedName :: Text -> ContainerRequest -> ContainerRequest
- setRandomName :: ContainerRequest -> ContainerRequest
- setCmd :: [Text] -> ContainerRequest -> ContainerRequest
- setVolumeMounts :: [(Text, Text)] -> ContainerRequest -> ContainerRequest
- setRm :: Bool -> ContainerRequest -> ContainerRequest
- setMemory :: Text -> ContainerRequest -> ContainerRequest
- setCpus :: Text -> ContainerRequest -> ContainerRequest
- withWorkingDirectory :: Text -> ContainerRequest -> ContainerRequest
- withNetwork :: Network -> ContainerRequest -> ContainerRequest
- withNetworkAlias :: Text -> ContainerRequest -> ContainerRequest
- setLink :: [ContainerId] -> ContainerRequest -> ContainerRequest
- setExpose :: [Port] -> ContainerRequest -> ContainerRequest
- setWaitingFor :: WaitUntilReady -> ContainerRequest -> ContainerRequest
- withFollowLogs :: LogConsumer -> ContainerRequest -> ContainerRequest
- consoleLogConsumer :: LogConsumer
- networkRequest :: NetworkRequest
- withDriver :: Text -> NetworkRequest -> NetworkRequest
- withIpv6 :: NetworkRequest -> NetworkRequest
- createNetwork :: NetworkRequest -> TestContainer Network
- fromExistingNetwork :: NetworkId -> TestContainer Network
- containerAlias :: Container -> Text
- containerGateway :: Container -> Text
- containerIp :: Container -> Text
- containerPort :: Container -> Port -> Int
- containerAddress :: Container -> Port -> (Text, Int)
- containerReleaseKey :: Container -> ReleaseKey
- containerImage :: Container -> Image
- inspect :: Container -> TestContainer InspectOutput
- kill :: Container -> TestContainer ()
- rm :: Container -> TestContainer ()
- withLogs :: Container -> (Handle -> Handle -> TestContainer a) -> TestContainer a
- waitUntilTimeout :: Int -> WaitUntilReady -> WaitUntilReady
- stateError :: State -> Maybe Text
- stateExitCode :: State -> Maybe Int
- stateFinishedAt :: State -> Maybe Text
- stateOOMKilled :: State -> Bool
- statePid :: State -> Maybe Int
- stateStartedAt :: State -> Maybe Text
- stateStatus :: State -> Status
- waitForState :: (State -> Bool) -> WaitUntilReady
- successfulExit :: State -> Bool
- waitWithLogs :: (Container -> Handle -> Handle -> IO ()) -> WaitUntilReady
- waitForLogLine :: Pipe -> (Text -> Bool) -> WaitUntilReady
- waitUntilMappedPortReachable :: Port -> WaitUntilReady
- waitForHttp :: Port -> String -> [Int] -> WaitUntilReady
- defaultDockerConfig :: Config
- determineConfig :: IO Config
- newTracer :: (Trace -> IO ()) -> Tracer
- dockerHostOs :: TestContainer Text
- isDockerOnLinux :: TestContainer Bool
- redis :: ToImage
- mongo :: ToImage
Tasty Ingredient
ingredient :: Ingredient Source #
Tasty Ingredient
that adds useful options to control defaults within the
TetContainers library.
main :: IO () main =defaultMainWithIngredients
(ingredient
:defaultIngredients
) tests
Since: 0.3.0.0
Running containers for tests
withContainers :: forall a. TestContainer a -> (IO a -> TestTree) -> TestTree Source #
Re-exports for convenience
Status of a Docker container.
Since: 0.5.0.0
Handle to a Docker image.
Since: 0.1.0.0
type LogConsumer = Pipe -> ByteString -> IO () Source #
An abstraction for forwarding logs.
Since: 0.5.0.0
type NetworkId = Text Source #
Identifies a network within the Docker runtime. Assigned by docker network create
Since: 0.5.0.0
Defintion of a Port
. Allows for specifying ports using various protocols. Due to the
Num
and IsString
instance allows for convenient Haskell literals.
>>>
"80" :: Port
80/tcp
>>>
"80/tcp" :: Port
80/tcp
>>>
80 :: Port
80/tcp
>>>
"90/udp" :: Port
90/udp
Instances
IsString Port Source # | A cursed but handy instance supporting literal Since: 0.5.0.0 |
Defined in TestContainers.Docker fromString :: String -> Port # | |
Num Port Source # | A cursed but handy instance supporting literal Since: 0.5.0.0 |
Show Port Source # | |
Eq Port Source # | |
Ord Port Source # | |
type InspectOutput = Value Source #
The parsed JSON output of docker inspect command.
Since: 0.1.0.0
data WaitUntilReady Source #
A strategy that describes how to asses readiness of a Container
. Allows
Users to plug in their definition of readiness.
Since: 0.1.0.0
Instances
Monoid WaitUntilReady Source # | Since: 0.5.0.0 |
Defined in TestContainers.Docker mappend :: WaitUntilReady -> WaitUntilReady -> WaitUntilReady # mconcat :: [WaitUntilReady] -> WaitUntilReady # | |
Semigroup WaitUntilReady Source # | Since: 0.5.0.0 |
Defined in TestContainers.Docker (<>) :: WaitUntilReady -> WaitUntilReady -> WaitUntilReady # sconcat :: NonEmpty WaitUntilReady -> WaitUntilReady # stimes :: Integral b => b -> WaitUntilReady -> WaitUntilReady # |
A data type indicating which pipe to scan for a specific log line.
Since: 0.1.0.0
type MonadDocker m = m ~ TestContainer Source #
Docker related functionality is parameterized over this Monad
. Since 0.5.0.0 this is
just a type alias for m ~
.TestContainer
Since: 0.1.0.0
data TestContainer a Source #
The heart and soul of the testcontainers library.
Since: 0.5.0.0
Instances
Configuration for defaulting behavior.
Since: 0.2.0.0
Config | |
|
Instances
MonadReader Config TestContainer Source # | |
Defined in TestContainers.Monad ask :: TestContainer Config # local :: (Config -> Config) -> TestContainer a -> TestContainer a # reader :: (Config -> a) -> TestContainer a # |
Traces execution within testcontainers library.
data DockerException Source #
Failing to interact with Docker results in this exception being thrown.
Since: 0.1.0.0
DockerException | |
InspectUnknownContainerId | |
| |
InspectOutputInvalidJSON | |
| |
InspectOutputMissingNetwork | |
| |
InspectOutputUnexpected | |
| |
UnknownPortMapping | |
|
Instances
Exception DockerException Source # | |
Defined in TestContainers.Docker.Internal | |
Show DockerException Source # | |
Defined in TestContainers.Docker.Internal showsPrec :: Int -> DockerException -> ShowS # show :: DockerException -> String # showList :: [DockerException] -> ShowS # | |
Eq DockerException Source # | |
Defined in TestContainers.Docker.Internal (==) :: DockerException -> DockerException -> Bool # (/=) :: DockerException -> DockerException -> Bool # |
newtype TimeoutException Source #
The exception thrown by waitUntilTimeout
.
Since: 0.1.0.0
TimeoutException | |
|
Instances
Exception TimeoutException Source # | |
Defined in TestContainers.Docker | |
Show TimeoutException Source # | |
Defined in TestContainers.Docker showsPrec :: Int -> TimeoutException -> ShowS # show :: TimeoutException -> String # showList :: [TimeoutException] -> ShowS # | |
Eq TimeoutException Source # | |
Defined in TestContainers.Docker (==) :: TimeoutException -> TimeoutException -> Bool # (/=) :: TimeoutException -> TimeoutException -> Bool # |
newtype UnexpectedEndOfPipe Source #
The exception thrown by waitForLine
in case the expected log line
wasn't found.
Since: 0.1.0.0
UnexpectedEndOfPipe | |
|
Instances
Exception UnexpectedEndOfPipe Source # | |
Defined in TestContainers.Docker | |
Show UnexpectedEndOfPipe Source # | |
Defined in TestContainers.Docker showsPrec :: Int -> UnexpectedEndOfPipe -> ShowS # show :: UnexpectedEndOfPipe -> String # showList :: [UnexpectedEndOfPipe] -> ShowS # | |
Eq UnexpectedEndOfPipe Source # | |
Defined in TestContainers.Docker (==) :: UnexpectedEndOfPipe -> UnexpectedEndOfPipe -> Bool # (/=) :: UnexpectedEndOfPipe -> UnexpectedEndOfPipe -> Bool # |
pattern TraceDockerInvocation :: [Text] -> Text -> ExitCode -> Trace Source #
The low-level invocation of docker
command
TraceDockerInvocation args stdin exitcode
pattern TraceDockerFollowLogs :: [Text] -> Trace Source #
Preparations to follow the logs for a certain container
pattern TraceDockerStdout :: Text -> Trace Source #
Line written to STDOUT by a Docker process.
pattern TraceDockerStderr :: Text -> Trace Source #
Line written to STDERR by a Docker process.
pattern TraceWaitUntilReady :: Maybe Int -> Trace Source #
Waiting for a container to become ready. Attached with the timeout to wait (in seconds).
pattern TraceOpenSocket :: Text -> Int -> Maybe IOException -> Trace Source #
Opening socket
stop :: Container -> TestContainer () Source #
Stops a Docker container. stop
is essentially docker stop
.
Since: 0.1.0.0
run :: ContainerRequest -> TestContainer Container Source #
Runs a Docker container from an Image
and ContainerRequest
. A finalizer
is registered so that the container is aways stopped when it goes out of scope.
This function is essentially docker run
.
Since: 0.1.0.0
build :: ToImage -> TestContainer ToImage Source #
Build the Image
referred to by the argument. If the construction of the
image is expensive (e.g. a call to fromBuildContext
) we don't want to
repeatedly build the image. Instead, build
can be used to execute the
underlying Docker build once and re-use the resulting Image
.
Since: 0.1.0.0
setEnv :: [(Text, Text)] -> ContainerRequest -> ContainerRequest Source #
Set the environment for the container. This is equivalent to passing --env key=value
to docker run
.
Since: 0.1.0.0
runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
NOTE Since version 1.2.0, this function will throw a
ResourceCleanupException
if any of the cleanup functions throw an
exception.
Since: resourcet-0.3.0
imageTag :: Image -> ImageTag Source #
The image tag assigned by Docker. Uniquely identifies an Image
within Docker.
Since: 0.1.0.0
fromImageId :: Text -> ToImage Source #
Get an Image
from an image id. This doesn't run docker pull
or any other Docker command
on construction.
Since: 0.5.1.0
fromBuildContext :: FilePath -> Maybe FilePath -> ToImage Source #
Build the image from a build path and an optional path to the Dockerfile (default is Dockerfile)
Since: 0.1.0.0
containerRequest :: ToImage -> ContainerRequest Source #
Default ContainerRequest
. Used as base for every Docker container.
Since: 0.1.0.0
withoutReaper :: WithoutReaper request => request -> request Source #
Do not register the docker resource (container, register, etc.) with the resource reaper. Careful, doing this will make your container leak on shutdown if not explicitly stopped.
Since: 0.5.1.0
setName :: Text -> ContainerRequest -> ContainerRequest Source #
Deprecated: See setFixedName
Set the name of a Docker container. This is equivalent to invoking docker run
with the --name
parameter.
Since: 0.1.0.0
setFixedName :: Text -> ContainerRequest -> ContainerRequest Source #
Set the name of a Docker container. This is equivalent to invoking docker run
with the --name
parameter.
Since: 0.5.0.0
setSuffixedName :: Text -> ContainerRequest -> ContainerRequest Source #
Set the name randomly suffixed of a Docker container. This is equivalent to invoking
docker run
with the --name
parameter.
Since: 0.5.0.0
setRandomName :: ContainerRequest -> ContainerRequest Source #
Set the name randomly given of a Docker container. This is equivalent to omitting
the --name
parameter calling docker run
.
Since: 0.5.0.0
setCmd :: [Text] -> ContainerRequest -> ContainerRequest Source #
The command to execute inside the Docker container. This is the equivalent
of passing the command on the docker run
invocation.
Since: 0.1.0.0
setVolumeMounts :: [(Text, Text)] -> ContainerRequest -> ContainerRequest Source #
The volume mounts to link to Docker container. This is the equivalent
of passing the command on the docker run -v
invocation.
setRm :: Bool -> ContainerRequest -> ContainerRequest Source #
Wether to remove the container once exited. This is equivalent to passing
--rm
to docker run
. (default is True
).
Since: 0.1.0.0
setMemory :: Text -> ContainerRequest -> ContainerRequest Source #
Set the memory limit of a Docker container. This is equivalent to
invoking docker run
with the --memory
parameter.
Since: 0.5.1.0
setCpus :: Text -> ContainerRequest -> ContainerRequest Source #
Set the cpus limit of a Docker container. This is equivalent to
invoking docker run
with the --cpus
parameter.
Since: 0.5.1.0
withWorkingDirectory :: Text -> ContainerRequest -> ContainerRequest Source #
Sets the working directory inside the container.
Since: 0.5.1.0
withNetwork :: Network -> ContainerRequest -> ContainerRequest Source #
Set the network the container will connect to. This is equivalent to passing
--network network_name
to docker run
.
Since: 0.5.0.0
withNetworkAlias :: Text -> ContainerRequest -> ContainerRequest Source #
Set the network alias for this container. This is equivalent to passing
--network-alias alias
to docker run
.
Since: 0.5.0.0
setLink :: [ContainerId] -> ContainerRequest -> ContainerRequest Source #
Set link on the container. This is equivalent to passing --link other_container
to docker run
.
Since: 0.1.0.0
setExpose :: [Port] -> ContainerRequest -> ContainerRequest Source #
Set exposed ports on the container. This is equivalent to setting --publish $PORT
to
docker run
. Docker assigns a random port for the host port. You will have to use containerIp
and containerPort
to connect to the published port.
container <-run
$containerRequest
redis
&setExpose
[ 6379 ] let (redisHost, redisPort) = (containerIp
container,containerPort
container 6379) print (redisHost, redisPort)
Since: 0.1.0.0
setWaitingFor :: WaitUntilReady -> ContainerRequest -> ContainerRequest Source #
Set the waiting strategy on the container. Depending on a Docker container
it can take some time until the provided service is ready. You will want to
use to setWaitingFor
to block until the container is ready to use.
Since: 0.1.0.0
withFollowLogs :: LogConsumer -> ContainerRequest -> ContainerRequest Source #
Forwards container logs to the given LogConsumer
once ran.
Since: 0.5.0.0
consoleLogConsumer :: LogConsumer Source #
A simple LogConsumer
that writes log lines to stdout and stderr respectively.
Since: 0.5.0.0
networkRequest :: NetworkRequest Source #
Default parameters for creating a new Docker network.
Since: 0.5.0.0
withDriver :: Text -> NetworkRequest -> NetworkRequest Source #
Driver to manage the Network (default "bridge").
Since: 0.5.0.0
withIpv6 :: NetworkRequest -> NetworkRequest Source #
Enable IPv6 for the Docker network.
Since: 0.5.0.0
createNetwork :: NetworkRequest -> TestContainer Network Source #
Creates a new Network
from a NetworkRequest
.
Since: 0.5.0.0
fromExistingNetwork :: NetworkId -> TestContainer Network Source #
Creates a Network
from an existing NetworkId
. Note that the Network
is
not managed by the TestContainer
monad and as such is not being cleaned up
afterwards.
Since: 0.5.1.0
containerAlias :: Container -> Text Source #
Get the container's network alias. Takes the first alias found.
Since: 0.5.0.0
containerGateway :: Container -> Text Source #
Get the IP address for the container's gateway, i.e. the host. Takes the first gateway address found.
Since: 0.5.0.0
containerIp :: Container -> Text Source #
Looks up the ip address of the container.
Since: 0.1.0.0
containerPort :: Container -> Port -> Int Source #
Looks up an exposed port on the host.
Since: 0.1.0.0
containerAddress :: Container -> Port -> (Text, Int) Source #
Returns the domain and port exposing the given container's port. Differs
from containerPort
in that containerAddress
will return the container's
domain and port if the program is running in the same network. Otherwise,
containerAddress
will use the exposed port on the Docker host.
Since: 0.5.0.0
containerReleaseKey :: Container -> ReleaseKey Source #
Deprecated: Containers are cleaned up with a separate resource reaper. Releasing the container manually is not going to work.
Returns the internal release key used for safely shutting down the container. Use this with care. This function is considered an internal detail.
Since: 0.1.0.0
containerImage :: Container -> Image Source #
Returns the underlying image of the container.
Since: 0.1.0.0
inspect :: Container -> TestContainer InspectOutput Source #
Runs the `docker inspect` command. Memoizes the result.
Since: 0.1.0.0
kill :: Container -> TestContainer () Source #
Kills a Docker container. kill
is essentially docker kill
.
Since: 0.1.0.0
rm :: Container -> TestContainer () Source #
Remove a Docker container. rm
is essentially docker rm -f
Since: 0.1.0.0
withLogs :: Container -> (Handle -> Handle -> TestContainer a) -> TestContainer a Source #
Access STDOUT and STDERR of a running Docker container. This is essentially
docker logs
under the hood.
Since: 0.1.0.0
waitUntilTimeout :: Int -> WaitUntilReady -> WaitUntilReady Source #
waitUntilTimeout n waitUntilReady
waits n
seconds for the container
to be ready. If the container is not ready by then a TimeoutException
will
be thrown.
Since: 0.1.0.0
stateOOMKilled :: State -> Bool Source #
Whether a container was killed by the OOM killer.
Since: 0.5.0.0
waitForState :: (State -> Bool) -> WaitUntilReady Source #
waitForState
waits for a certain state of the container. If the container reaches a terminal
state InvalidStateException
will be thrown.
Since: 0.5.0.0
successfulExit :: State -> Bool Source #
successfulExit
is supposed to be used in conjunction with waitForState
.
Since: 0.5.0.0
waitWithLogs :: (Container -> Handle -> Handle -> IO ()) -> WaitUntilReady Source #
A low-level primitive that allows scanning the logs for specific log lines that indicate readiness of a container.
The Handle
s passed to the function argument represent stdout
and stderr
of the container.
Since: 0.1.0.0
waitForLogLine :: Pipe -> (Text -> Bool) -> WaitUntilReady Source #
Waits for a specific line to occur in the logs. Throws a UnexpectedEndOfPipe
exception in case the desired line can not be found on the logs.
Say you want to find "Ready to accept connections" in the logs on Stdout try:
waitForLogLine Stdout ("Ready to accept connections" `isInfixOf`
)
Since: 0.1.0.0
waitUntilMappedPortReachable :: Port -> WaitUntilReady Source #
Waits until the port of a container is ready to accept connections.
This combinator should always be used with waitUntilTimeout
.
Since: 0.1.0.0
:: Port | Port |
-> String | URL path |
-> [Int] | Acceptable status codes |
-> WaitUntilReady |
Waits for a specific http status code.
This combinator should always be used with waitUntilTimeout
.
Since: 0.5.0.0
defaultDockerConfig :: Config Source #
Default configuration.
Since: 0.2.0.0
determineConfig :: IO Config Source #
Autoselect the default configuration depending on wether you use Docker For Mac or not.