Copyright | 2018 Automattic Inc. |
---|---|
License | GPL-3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Test.Tasty.WebDriver
Description
Tasty integration for WebDriverT
tests.
- defaultWebDriverMain :: TestTree -> IO ()
- testCase :: TestName -> WebDriver IO () -> TestTree
- testCaseM :: (Monad eff, Typeable eff) => TestName -> (forall a. P WDAct a -> eff a) -> (forall a. eff a -> IO a) -> WebDriver eff () -> TestTree
- testCaseT :: (Monad (m IO), Typeable m) => TestName -> (forall a. IO a -> m IO a) -> (forall a. m IO a -> IO a) -> WebDriverT (m IO) () -> TestTree
- testCaseTM :: (Monad eff, Monad (m eff), Typeable eff, Typeable m) => TestName -> (forall a. P WDAct a -> eff a) -> (forall a. eff a -> m eff a) -> (forall a. m eff a -> IO a) -> WebDriverT (m eff) () -> TestTree
- testCaseWithSetup :: TestName -> WebDriver IO u -> (v -> WebDriver IO ()) -> (u -> WebDriver IO v) -> TestTree
- testCaseWithSetupM :: (Monad eff, Typeable eff) => TestName -> (forall u. P WDAct u -> eff u) -> (forall u. eff u -> IO u) -> WebDriver eff u -> (v -> WebDriver eff ()) -> (u -> WebDriver eff v) -> TestTree
- testCaseWithSetupT :: (Monad (m IO), Typeable m) => TestName -> (forall a. IO a -> m IO a) -> (forall a. m IO a -> IO a) -> WebDriverT (m IO) u -> (v -> WebDriverT (m IO) ()) -> (u -> WebDriverT (m IO) v) -> TestTree
- testCaseWithSetupTM :: (Monad eff, Monad (m eff), Typeable eff, Typeable m) => TestName -> (forall a. P WDAct a -> eff a) -> (forall a. eff a -> m eff a) -> (forall a. m eff a -> IO a) -> WebDriverT (m eff) u -> (v -> WebDriverT (m eff) ()) -> (u -> WebDriverT (m eff) v) -> TestTree
- ifDriverIs :: DriverName -> (TestTree -> TestTree) -> TestTree -> TestTree
- ifTierIs :: DeploymentTier -> (TestTree -> TestTree) -> TestTree -> TestTree
- ifHeadless :: (TestTree -> TestTree) -> TestTree -> TestTree
- unlessDriverIs :: DriverName -> (TestTree -> TestTree) -> TestTree -> TestTree
- unlessTierIs :: DeploymentTier -> (TestTree -> TestTree) -> TestTree -> TestTree
- unlessHeadless :: (TestTree -> TestTree) -> TestTree -> TestTree
- newtype Driver = Driver {}
- data DriverName
- newtype DataPath = DataPath {}
- newtype Deployment = Deployment {}
- data DeploymentTier
- newtype BrowserPath = BrowserPath {}
- newtype ApiResponseFormat = ApiResponseFormat {}
- newtype WebDriverApiVersion = WebDriverApiVersion {}
- newtype LogHandle = LogHandle {}
- newtype TestDelay = TestDelay {
- theTestDelay :: Int
- newtype NumRetries = NumRetries {
- theNumRetries :: Int
- data LogNoiseLevel
- newtype ConsoleInHandle = ConsoleInHandle {}
- newtype ConsoleOutHandle = ConsoleOutHandle {}
- newtype RemoteEndRef = RemoteEndRef {}
- newtype Headless = Headless {
- theHeadless :: Bool
- newtype LogColors = LogColors {
- theLogColors :: Bool
- newtype GeckodriverLog = GeckodriverLog {}
- module Test.Tasty.WebDriver.Config
Documentation
defaultWebDriverMain :: TestTree -> IO () Source #
Run a tree of webdriver tests. Thin wrapper around tasty's defaultMain
that attempts to determine the deployment tier and interprets remote end config command line options.
Test Case Constructors
Arguments
:: (Monad eff, Typeable eff) | |
=> TestName | |
-> (forall a. P WDAct a -> eff a) | Evaluator |
-> (forall a. eff a -> IO a) | Conversion to |
-> WebDriver eff () | |
-> TestTree |
WebDriver
test case with a custom effect evaluator.
Arguments
:: (Monad (m IO), Typeable m) | |
=> TestName | |
-> (forall a. IO a -> m IO a) | Lift effects to the inner monad |
-> (forall a. m IO a -> IO a) | Conversion to |
-> WebDriverT (m IO) () | The test |
-> TestTree |
WebDriverT
test case with the default IO
effect evaluator.
Arguments
:: (Monad eff, Monad (m eff), Typeable eff, Typeable m) | |
=> TestName | |
-> (forall a. P WDAct a -> eff a) | Evaluator |
-> (forall a. eff a -> m eff a) | Lift effects to the inner monad |
-> (forall a. m eff a -> IO a) | Conversion to |
-> WebDriverT (m eff) () | The test |
-> TestTree |
WebDriverT
test case with a custom effect evaluator.
Arguments
:: (Monad eff, Typeable eff) | |
=> TestName | |
-> (forall u. P WDAct u -> eff u) | Evaluator |
-> (forall u. eff u -> IO u) | Conversion to |
-> WebDriver eff u | Setup |
-> (v -> WebDriver eff ()) | Teardown |
-> (u -> WebDriver eff v) | The test |
-> TestTree |
WebDriver
test case with additional setup and teardown phases and a custom effect evaluator. Setup runs before the test (for e.g. logging in) and teardown runs after the test (for e.g. deleting temp files).
Arguments
:: (Monad (m IO), Typeable m) | |
=> TestName | |
-> (forall a. IO a -> m IO a) | Lift effects to the inner monad |
-> (forall a. m IO a -> IO a) | Conversion to |
-> WebDriverT (m IO) u | Setup |
-> (v -> WebDriverT (m IO) ()) | Teardown |
-> (u -> WebDriverT (m IO) v) | Test |
-> TestTree |
WebDriverT
test case with additional setup and teardown phases using the default IO
effect evaluator. Setup runs before the test (for e.g. logging in) and teardown runs after the test (for e.g. deleting temp files).
Arguments
:: (Monad eff, Monad (m eff), Typeable eff, Typeable m) | |
=> TestName | |
-> (forall a. P WDAct a -> eff a) | Evaluator |
-> (forall a. eff a -> m eff a) | Lift effects to the inner monad |
-> (forall a. m eff a -> IO a) | Conversion to |
-> WebDriverT (m eff) u | Setup |
-> (v -> WebDriverT (m eff) ()) | Teardown |
-> (u -> WebDriverT (m eff) v) | Test |
-> TestTree |
WebDriverT
test case with additional setup and teardown phases and a custom effect evaluator. Setup runs before the test (for logging in, say) and teardown runs after the test (for deleting temp files, say).
Branching
ifDriverIs :: DriverName -> (TestTree -> TestTree) -> TestTree -> TestTree Source #
Set local options if the Driver
option is a given value.
ifTierIs :: DeploymentTier -> (TestTree -> TestTree) -> TestTree -> TestTree Source #
Set local options if the Deployment
option is a given value.
ifHeadless :: (TestTree -> TestTree) -> TestTree -> TestTree Source #
Set local options if Headless
is true.
unlessDriverIs :: DriverName -> (TestTree -> TestTree) -> TestTree -> TestTree Source #
Set local options if the Driver
option is not a given value.
unlessTierIs :: DeploymentTier -> (TestTree -> TestTree) -> TestTree -> TestTree Source #
Set local options if the Deployment
option is not a given value.
unlessHeadless :: (TestTree -> TestTree) -> TestTree -> TestTree Source #
Set local options if Headless
is false.
Options
Remote end name.
Constructors
Driver | |
Fields |
Path where secrets are stored.
Constructors
DataPath | |
Fields |
data DeploymentTier Source #
Representation of the deployment environment.
Constructors
DEV | Local environment |
TEST | CI server (for testing the library) |
PROD | Production -- e.g. testing a real site |
Instances
newtype ApiResponseFormat Source #
Expected API response format.
Constructors
ApiResponseFormat | |
Fields |
Instances
newtype WebDriverApiVersion Source #
WebDriver API version.
Constructors
WebDriverApiVersion | |
Fields |
Instances
Log location.
Constructors
LogHandle | |
Fields |
Delay between test attempts.
Constructors
TestDelay | |
Fields
|
newtype NumRetries Source #
Max number of retries.
Constructors
NumRetries | |
Fields
|
Instances
newtype ConsoleInHandle Source #
Console in location. Used to mock stdin for testing.
Constructors
ConsoleInHandle | |
Fields |
Instances
newtype ConsoleOutHandle Source #
Console out location. Used to mock stdout for testing.
Constructors
ConsoleOutHandle | |
Fields |
Instances
Run in headless mode.
Constructors
Headless | |
Fields
|
Governs whether logs are printed in color
Constructors
LogColors | |
Fields
|
newtype GeckodriverLog Source #
Verbosity level passed to geckodriver
Constructors
GeckodriverLog | |
Fields |
Instances
module Test.Tasty.WebDriver.Config