Copyright | 2018 Automattic Inc. |
---|---|
License | GPL-3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Tasty integration for WebDriverT
tests.
Synopsis
- defaultWebDriverMain :: TestTree -> IO ()
- testCase :: TestName -> WebDriverT IO () -> TestTree
- testCaseM :: (Monad eff, Typeable eff) => TestName -> (forall a. P WDAct a -> eff a) -> (forall a. eff a -> IO a) -> WebDriverT eff () -> TestTree
- testCaseT :: (Monad (t IO), MonadTrans t, Typeable t) => TestName -> (forall a. t IO a -> IO a) -> WebDriverTT t IO () -> TestTree
- testCaseTM :: (Monad eff, Monad (t eff), MonadTrans t, Typeable eff, Typeable t) => TestName -> (forall a. P WDAct a -> eff a) -> (forall a. t eff a -> IO a) -> WebDriverTT t eff () -> TestTree
- testCaseWithSetup :: TestName -> WebDriverT IO u -> (v -> WebDriverT IO ()) -> (u -> WebDriverT IO v) -> TestTree
- testCaseWithSetupM :: (Monad eff, Typeable eff) => TestName -> (forall u. P WDAct u -> eff u) -> (forall u. eff u -> IO u) -> WebDriverT eff u -> (v -> WebDriverT eff ()) -> (u -> WebDriverT eff v) -> TestTree
- testCaseWithSetupT :: (Monad (t IO), MonadTrans t, Typeable t) => TestName -> (forall a. t IO a -> IO a) -> WebDriverTT t IO u -> (v -> WebDriverTT t IO ()) -> (u -> WebDriverTT t IO v) -> TestTree
- testCaseWithSetupTM :: (Monad eff, Monad (t eff), MonadTrans t, Typeable eff, Typeable t) => TestName -> (forall a. P WDAct a -> eff a) -> (forall a. t eff a -> IO a) -> WebDriverTT t eff u -> (v -> WebDriverTT t eff ()) -> (u -> WebDriverTT t 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 {}
- newtype PrivateMode = PrivateMode {}
- module Test.Tasty.WebDriver.Config
Documentation
defaultWebDriverMain :: TestTree -> IO () Source #
Run a tree of WebDriverT 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
:: TestName | |
-> WebDriverT IO () | The test |
-> TestTree |
WebDriver
test case with the default IO
effect evaluator.
:: (Monad eff, Typeable eff) | |
=> TestName | |
-> (forall a. P WDAct a -> eff a) | Evaluator |
-> (forall a. eff a -> IO a) | Conversion to |
-> WebDriverT eff () | |
-> TestTree |
WebDriver
test case with a custom effect evaluator.
:: (Monad (t IO), MonadTrans t, Typeable t) | |
=> TestName | |
-> (forall a. t IO a -> IO a) | Conversion to |
-> WebDriverTT t IO () | The test |
-> TestTree |
WebDriverT
test case with the default IO
effect evaluator.
:: (Monad eff, Monad (t eff), MonadTrans t, Typeable eff, Typeable t) | |
=> TestName | |
-> (forall a. P WDAct a -> eff a) | Evaluator |
-> (forall a. t eff a -> IO a) | Conversion to |
-> WebDriverTT t eff () | The test |
-> TestTree |
WebDriverT
test case with a custom effect evaluator.
:: TestName | |
-> WebDriverT IO u | Setup |
-> (v -> WebDriverT IO ()) | Teardown |
-> (u -> WebDriverT IO v) | The test |
-> TestTree |
WebDriver
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).
:: (Monad eff, Typeable eff) | |
=> TestName | |
-> (forall u. P WDAct u -> eff u) | Evaluator |
-> (forall u. eff u -> IO u) | Conversion to |
-> WebDriverT eff u | Setup |
-> (v -> WebDriverT eff ()) | Teardown |
-> (u -> WebDriverT 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).
:: (Monad (t IO), MonadTrans t, Typeable t) | |
=> TestName | |
-> (forall a. t IO a -> IO a) | Conversion to |
-> WebDriverTT t IO u | Setup |
-> (v -> WebDriverTT t IO ()) | Teardown |
-> (u -> WebDriverTT t 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).
:: (Monad eff, Monad (t eff), MonadTrans t, Typeable eff, Typeable t) | |
=> TestName | |
-> (forall a. P WDAct a -> eff a) | Evaluator |
-> (forall a. t eff a -> IO a) | Conversion to |
-> WebDriverTT t eff u | Setup |
-> (v -> WebDriverTT t eff ()) | Teardown |
-> (u -> WebDriverTT t 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.
Instances
IsOption Driver Source # | |
Defined in Test.Tasty.WebDriver defaultValue :: Driver # parseValue :: String -> Maybe Driver # optionName :: Tagged Driver String # |
data DriverName Source #
Remote end name.
Instances
Eq DriverName Source # | |
Defined in Test.Tasty.WebDriver.Config (==) :: DriverName -> DriverName -> Bool # (/=) :: DriverName -> DriverName -> Bool # | |
Ord DriverName Source # | |
Defined in Test.Tasty.WebDriver.Config compare :: DriverName -> DriverName -> Ordering # (<) :: DriverName -> DriverName -> Bool # (<=) :: DriverName -> DriverName -> Bool # (>) :: DriverName -> DriverName -> Bool # (>=) :: DriverName -> DriverName -> Bool # max :: DriverName -> DriverName -> DriverName # min :: DriverName -> DriverName -> DriverName # | |
Show DriverName Source # | |
Defined in Test.Tasty.WebDriver.Config showsPrec :: Int -> DriverName -> ShowS # show :: DriverName -> String # showList :: [DriverName] -> ShowS # |
Path where secrets are stored.
Instances
IsOption DataPath Source # | |
Defined in Test.Tasty.WebDriver |
newtype Deployment Source #
Named deployment environment.
Instances
Eq Deployment Source # | |
Defined in Test.Tasty.WebDriver (==) :: Deployment -> Deployment -> Bool # (/=) :: Deployment -> Deployment -> Bool # | |
IsOption Deployment Source # | |
Defined in Test.Tasty.WebDriver |
data DeploymentTier Source #
Representation of the deployment environment.
DEV | Local environment |
TEST | CI server (for testing the library) |
PROD | Production -- e.g. testing a real site |
Instances
Eq DeploymentTier Source # | |
Defined in Test.Tasty.WebDriver (==) :: DeploymentTier -> DeploymentTier -> Bool # (/=) :: DeploymentTier -> DeploymentTier -> Bool # | |
Show DeploymentTier Source # | |
Defined in Test.Tasty.WebDriver showsPrec :: Int -> DeploymentTier -> ShowS # show :: DeploymentTier -> String # showList :: [DeploymentTier] -> ShowS # |
newtype BrowserPath Source #
Path to browser binary.
Instances
IsOption BrowserPath Source # | |
Defined in Test.Tasty.WebDriver |
newtype ApiResponseFormat Source #
Expected API response format.
Instances
IsOption ApiResponseFormat Source # | |
newtype WebDriverApiVersion Source #
WebDriver API version.
Instances
IsOption WebDriverApiVersion Source # | |
Log location.
Instances
IsOption LogHandle Source # | |
Defined in Test.Tasty.WebDriver |
Delay between test attempts.
newtype NumRetries Source #
Max number of retries.
Instances
IsOption NumRetries Source # | |
Defined in Test.Tasty.WebDriver |
data LogNoiseLevel Source #
Log Noise Level.
Instances
IsOption LogNoiseLevel Source # | |
Defined in Test.Tasty.WebDriver |
newtype ConsoleInHandle Source #
Console in location. Used to mock stdin for testing.
Instances
IsOption ConsoleInHandle Source # | |
newtype ConsoleOutHandle Source #
Console out location. Used to mock stdout for testing.
Instances
IsOption ConsoleOutHandle Source # | |
newtype RemoteEndRef Source #
Mutable remote end pool
Instances
IsOption RemoteEndRef Source # | |
Defined in Test.Tasty.WebDriver |
Run in headless mode.
Instances
IsOption Headless Source # | |
Defined in Test.Tasty.WebDriver |
Governs whether logs are printed in color
Instances
IsOption LogColors Source # | |
Defined in Test.Tasty.WebDriver |
newtype GeckodriverLog Source #
Verbosity level passed to geckodriver
Instances
IsOption GeckodriverLog Source # | |
newtype PrivateMode Source #
Run in private mode.
Instances
IsOption PrivateMode Source # | |
Defined in Test.Tasty.WebDriver |
module Test.Tasty.WebDriver.Config