tasty-tmux-0.1.0.5: Terminal user acceptance testing (UAT) via tmux
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Tasty.Tmux

Description

This module provides a test framework for user acceptance testing (UAT) of command line or console applications. The framework establishes tmux sessions for test cases and provides functions for sending input to the tmux session and making assertions about the state of the terminal (i.e. what is on the screen).

Synopsis

User guide

Synopsis

Test cases (TestCase) are defined using withTmuxSession. The testTmux function groups test cases into a Tasty TestTree. Test cases are executed sequentially, each in a separate tmux session. Each test case can have a setup and teardown action, and there can also be a setup and teardown around the whole group of tests.

Let's look at a specific usage example. You want to test some program. There are two tests. Each test needs a dedicated temporary directory, but they also need a separate, shared temporary directory. We want the setup routines to create these directories and the teardown routines to remove them. Assume the existence of mkTempDir :: IO FilePath and rmDir :: FilePath -> IO ().

Looking first at testTmux:

data SharedEnv = SharedEnv FilePath

myTests :: TestTree
myTests = testTmux pre post [test1, test2]
  where
  pre = SharedEnv <$> mkTempDir
  post (SharedEnv path) = rmDir path

The shared setup action pre returns a SharedEnv value that will be propagated to each test case, as well as the teardown action, after all test cases have run.

test1 and test2 are defined thus:

test1 :: TestCase SharedEnv
test1 = withTmuxSession setup teardown "putFile" $ \step -> do
  -- test environment is availabe via ask
  TestEnv _ sharedDir testDir <- ask

  -- send a command to the tmux session and wait for "Done"
  sendLine ("myProg putFile " <> sharedDir) (Substring "Done.")

  -- save a snapshot of the terminal state and make some assertions
  snapshot
  assertSubstringS "The output should contain this substring"
  assertRegexS "The output should match this [Rr]eg[Ee]x"

test2 :: TestCase SharedEnv
test2 = withTmuxSession setup teardown "checkFile" $ \step -> do
  TestEnv _ sharedDir testDir <- ask

  -- use step to label different stages of the test
  step "Run program"
  sendLine ("myProg checkFile " <> sharedDir) (Substring "Yep, it's there.")

  step "Check exit code"
  sendLine "echo status $?" (Substring "status 0")

Further discussion of the setup action is warranted. This function, at minimum, must incorporate the TmuxSession argument into the value it returns. The type it returns must have an instance of HasTmuxSession; this provides the name of the tmux session to the framework functions that interact with tmux.

In our example, it also creates a per-test case temporary directory. The value returned by the setup action is provided to the teardown action.

data TestEnv = TestEnv
  { _session    :: TmuxSession
  , _sharedDir  :: FilePath
  , _testDir    :: FilePath
  }

instance HasTmuxSession TestEnv where
  tmuxSession = lens _session (\s b -> s { _session = b })

setup :: SharedEnv -> TmuxSession -> IO TestEnv
setup (SharedEnv sharedDir) session = TestEnv session sharedDir <$> mkTempDir

teardown :: TestEnv -> IO ()
teardown (TestEnv _ _ testDir) = rmDir testDir

If either shared or test-specific setup and teardown are not needed, the testTmux' and withTmuxSession' functions are provided for convenience.

Terminal character encoding

tasty-tmux does not make any assumptions about terminal character encoding. The only exception is captureString which assumes UTF-8 encoding. All other functions deal with ByteString.

Be careful when using OverloadedStrings - the IsString instance for ByteString messes up characters > 127. If you need to include high characters in String or Regex assertions, encoding them using the expected terminal character encoding (you can encode in UTF-8 via encodeUtf8).

API documentation

Creating test cases

testTmux Source #

Arguments

:: IO a

Set-up action. Executed one time, after the keepalive session is created but before any test cases are executed.

-> (a -> IO ())

Tear-down action. Executed after all test cases have finished but before the keepalive session gets killed.

-> [TestCase a] 
-> TestTree 

Run a series of tests in tmux sessions.

Tests are executed sequentially. Each test case is executed in a new tmux session. The name of the session is derived from the name of the test and prepended with the sequence number.

A session called "keepalive" is created before any test cases are run, and killed after all the test cases have finished. This session ensures that the tmux server remains alive, avoiding some race conditions.

testTmux' :: [TestCase ()] -> TestTree Source #

Like testTmux but with no setup or teardown

withTmuxSession Source #

Arguments

:: HasTmuxSession testEnv 
=> (sharedEnv -> TmuxSession -> IO testEnv)

Set up session. The tmux session is established before this action is run. Takes the shared environment and Tmux session and constructs a test environment value (which must make the TmuxSession available via its HasTmuxSession instance).

-> (testEnv -> IO ())

Tear down the session. The tmux session will be torn down after this action.

-> TestName

Name of the test (a string).

-> (forall m. (MonadReader testEnv m, MonadState Capture m, MonadIO m) => (String -> m ()) -> m a)

The main test function. The argument is the "step" function which can be called with a description to label the steps of the test procedure.

-> TestCase sharedEnv 

Run all application steps in a session defined by session name.

withTmuxSession' Source #

Arguments

:: TestName 
-> (forall m. (MonadReader TmuxSession m, MonadState Capture m, MonadIO m) => (String -> m ()) -> m a)

The main test function. The argument is the "step" function which can be called with a description to label the steps of the test procedure.

-> TestCase sharedEnv 

Like withTmuxSession but without setup and teardown. Shared environment value (and its type) is ignored.

type TestCase a = IO a -> Int -> TestTree Source #

A test case that will be executed in a dedicated tmux session. Parameterised over the shared environment type.

Test environment

class HasTmuxSession a where Source #

This class provides access to a tmux session name. Test environment types must have an instance of this class.

Methods

tmuxSession :: Functor f => (TmuxSession -> f TmuxSession) -> a -> f a Source #

Lens to the TmuxSession

Instances

Instances details
HasTmuxSession TmuxSession Source # 
Instance details

Defined in Test.Tasty.Tmux

type TmuxSession = String Source #

tmux session name

Sending input to a session

sendKeys :: (HasTmuxSession a, MonadReader a m, MonadIO m) => String -> Condition -> m Capture Source #

Send interpreted keys into the program and wait for the condition to be met, failing the test if the condition is not met after some time.

sendLiteralKeys :: (HasTmuxSession a, MonadReader a m, MonadIO m) => String -> Condition -> m Capture Source #

Send literal keys to the terminal and wait for the condition to be satisfied, with default timeout.

sendLine :: (HasTmuxSession a, MonadReader a m, MonadIO m) => String -> Condition -> m Capture Source #

Send the literal string to the terminal, followed by Enter, then wait for the condition be satisfied, with default timeout.

tmuxSendKeys :: (HasTmuxSession a, MonadReader a m, MonadIO m) => TmuxKeysMode -> String -> m () Source #

Send keystrokes into a tmux session.

data TmuxKeysMode Source #

Whether to tell tmux to treat keys literally or interpret sequences like Enter or "C-x".

Constructors

LiteralKeys 
InterpretKeys 

Instances

Instances details
Eq TmuxKeysMode Source # 
Instance details

Defined in Test.Tasty.Tmux

setEnvVarInSession :: (HasTmuxSession a, MonadReader a m, MonadIO m) => String -> String -> m () Source #

Sets a shell environment variable.

Note: The tmux program provides a command to set environment variables for running sessions, yet they seem to be not inherited by the shell.

This assumes that a standard shell prompt is ready in the session. No attempt is made to check this; it just blindly send they keystrokes.

Capturing terminal state

capture :: (HasTmuxSession a, MonadReader a m, MonadIO m) => m Capture Source #

Capture the current terminal state.

snapshot :: (HasTmuxSession a, MonadReader a m, MonadState Capture m, MonadIO m) => m () Source #

Snapshot the current terminal state.

snapshot = capture >>= put

Use functions like assertConditionS to make assertions on the most recent snapshot.

data Capture Source #

A captured pane. For now this just contains the string content, but in the future perhaps we will augment it with terminal title, terminal dimensions, timestamp, etc.

Use captureBytes to get the raw terminal output.

captureBytes :: Capture -> ByteString Source #

Get the raw bytes of the capture, including escape sequences.

captureString :: Capture -> String Source #

Get the captured terminal content as a string, including escape sequences. Assumes UTF-8 encoding and uses replacement characters for bad encoding or unknown code points.

Assertions

waitForCondition Source #

Arguments

:: (HasTmuxSession a, MonadReader a m, MonadIO m) 
=> Condition 
-> Int

Number of retries allowed

-> Int

Initial microseconds to back off. Multiplied by 4 on each retry.

-> m Capture

Return the successful capture (or throw an exception)

Capture the pane and check for a condition, optionally retrying with exponential backoff. If the condition is not met after the final attempt, the test fails.

data Condition Source #

A condition to check for in the output of the program

Instances

Instances details
Show Condition Source # 
Instance details

Defined in Test.Tasty.Tmux

defaultBackoff :: Int Source #

20 milliseconds

assertCondition :: MonadIO m => Condition -> Capture -> m () Source #

Assert that the capture satisfies a condition

assertSubstring :: MonadIO m => ByteString -> Capture -> m () Source #

Substring assertion.

assertRegex :: MonadIO m => ByteString -> Capture -> m () Source #

Regex assertion.

State-aware assertions

assertConditionS :: (MonadIO m, MonadState Capture m) => Condition -> m () Source #

Assert that the saved capture satisfies a condition.

Use snapshot to save a capture:

snapshot
assertConditionS (Regex "[Ff][Oo][Oo]")

Alternatively, use put on the result of any action that returns a Capture:

sendKeys Enter Unconditional >>= put
assertConditionS (Substring "Doing thing...")

See also assertSubstringS and assertRegexS.

assertSubstringS :: (MonadIO m, MonadState Capture m) => ByteString -> m () Source #

State-aware substring assertion.

assertRegexS :: (MonadIO m, MonadState Capture m) => ByteString -> m () Source #

State-aware regex assertion.

ANSI escape sequence regex helpers

type AnsiAttrParam = String Source #

ANSI attribute

type AnsiFGParam = String Source #

ANSI foreground colour

type AnsiBGParam = String Source #

ANSI background colour

buildAnsiRegex :: [AnsiAttrParam] -> [AnsiFGParam] -> [AnsiBGParam] -> ByteString Source #

Generate a regex for an escape sequence, setting the given foreground and background parameters.

tmux < 03d01ea (first released in tmux-2.5) ran attributes, foreground colour and background colour params separated by semicolons (foreground first). After that commit, attributes, foreground colours and background colours are written in separate escape sequences. Therefore for compatibility with different versions of tmux there are two patterns to check.

Re-exports

put :: MonadState s m => s -> m () #

Replace the state inside the monad.