| 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.
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 a. P WDAct a -> eff a) -> (forall a. eff a -> IO a) -> 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
Arguments
| :: TestName | |
| -> WebDriverT IO () | The test |
| -> TestTree |
WebDriver test case with the default IO effect evaluator.
Arguments
| :: (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.
Arguments
| :: (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.
Arguments
| :: (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.
Arguments
| :: 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).
Arguments
| :: (Monad eff, Typeable eff) | |
| => TestName | |
| -> (forall a. P WDAct a -> eff a) | Evaluator |
| -> (forall a. eff a -> IO a) | 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).
Arguments
| :: (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).
Arguments
| :: (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.
Constructors
| Driver | |
Fields | |
Instances
| IsOption Driver Source # | |
Defined in Test.Tasty.WebDriver Methods defaultValue :: Driver # parseValue :: String -> Maybe Driver # optionName :: Tagged Driver String # optionHelp :: Tagged Driver String # showDefaultValue :: Driver -> Maybe String # | |
data DriverName Source #
Remote end name.
Constructors
| Geckodriver | |
| Chromedriver |
Instances
| Eq DriverName Source # | |
Defined in Test.Tasty.WebDriver.Config | |
| Ord DriverName Source # | |
Defined in Test.Tasty.WebDriver.Config Methods 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 Methods showsPrec :: Int -> DriverName -> ShowS # show :: DriverName -> String # showList :: [DriverName] -> ShowS # | |
Path where secrets are stored.
Constructors
| DataPath | |
Fields | |
Instances
| IsOption DataPath Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe DataPath # optionName :: Tagged DataPath String # optionHelp :: Tagged DataPath String # showDefaultValue :: DataPath -> Maybe String # | |
newtype Deployment Source #
Named deployment environment.
Constructors
| Deployment | |
Fields | |
Instances
| Eq Deployment Source # | |
Defined in Test.Tasty.WebDriver | |
| IsOption Deployment Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe Deployment # optionName :: Tagged Deployment String # optionHelp :: Tagged Deployment String # showDefaultValue :: Deployment -> Maybe String # | |
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
| Eq DeploymentTier Source # | |
Defined in Test.Tasty.WebDriver Methods (==) :: DeploymentTier -> DeploymentTier -> Bool # (/=) :: DeploymentTier -> DeploymentTier -> Bool # | |
| Show DeploymentTier Source # | |
Defined in Test.Tasty.WebDriver Methods showsPrec :: Int -> DeploymentTier -> ShowS # show :: DeploymentTier -> String # showList :: [DeploymentTier] -> ShowS # | |
newtype BrowserPath Source #
Path to browser binary.
Constructors
| BrowserPath | |
Fields | |
Instances
| IsOption BrowserPath Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe BrowserPath # optionName :: Tagged BrowserPath String # optionHelp :: Tagged BrowserPath String # showDefaultValue :: BrowserPath -> Maybe String # | |
newtype ApiResponseFormat Source #
Expected API response format.
Constructors
| ApiResponseFormat | |
Fields | |
Instances
| IsOption ApiResponseFormat Source # | |
Defined in Test.Tasty.WebDriver | |
newtype WebDriverApiVersion Source #
WebDriver API version.
Constructors
| WebDriverApiVersion | |
Fields | |
Instances
| IsOption WebDriverApiVersion Source # | |
Defined in Test.Tasty.WebDriver | |
Log location.
Constructors
| LogHandle | |
Fields | |
Instances
| IsOption LogHandle Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe LogHandle # optionName :: Tagged LogHandle String # optionHelp :: Tagged LogHandle String # showDefaultValue :: LogHandle -> Maybe String # | |
Delay between test attempts.
Constructors
| TestDelay | |
Fields
| |
newtype NumRetries Source #
Max number of retries.
Constructors
| NumRetries | |
Fields
| |
Instances
| IsOption NumRetries Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe NumRetries # optionName :: Tagged NumRetries String # optionHelp :: Tagged NumRetries String # showDefaultValue :: NumRetries -> Maybe String # | |
data LogNoiseLevel Source #
Log Noise Level.
Instances
| IsOption LogNoiseLevel Source # | |
Defined in Test.Tasty.WebDriver Methods defaultValue :: LogNoiseLevel # parseValue :: String -> Maybe LogNoiseLevel # optionName :: Tagged LogNoiseLevel String # optionHelp :: Tagged LogNoiseLevel String # | |
newtype ConsoleInHandle Source #
Console in location. Used to mock stdin for testing.
Constructors
| ConsoleInHandle | |
Fields | |
Instances
| IsOption ConsoleInHandle Source # | |
Defined in Test.Tasty.WebDriver | |
newtype ConsoleOutHandle Source #
Console out location. Used to mock stdout for testing.
Constructors
| ConsoleOutHandle | |
Fields | |
Instances
| IsOption ConsoleOutHandle Source # | |
Defined in Test.Tasty.WebDriver | |
newtype RemoteEndRef Source #
Mutable remote end pool
Constructors
| RemoteEndRef | |
Fields | |
Instances
| IsOption RemoteEndRef Source # | |
Defined in Test.Tasty.WebDriver Methods defaultValue :: RemoteEndRef # parseValue :: String -> Maybe RemoteEndRef # optionName :: Tagged RemoteEndRef String # optionHelp :: Tagged RemoteEndRef String # showDefaultValue :: RemoteEndRef -> Maybe String # | |
Run in headless mode.
Constructors
| Headless | |
Fields
| |
Instances
| IsOption Headless Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe Headless # optionName :: Tagged Headless String # optionHelp :: Tagged Headless String # showDefaultValue :: Headless -> Maybe String # | |
Governs whether logs are printed in color
Constructors
| LogColors | |
Fields
| |
Instances
| IsOption LogColors Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe LogColors # optionName :: Tagged LogColors String # optionHelp :: Tagged LogColors String # showDefaultValue :: LogColors -> Maybe String # | |
newtype GeckodriverLog Source #
Verbosity level passed to geckodriver
Constructors
| GeckodriverLog | |
Fields | |
Instances
| IsOption GeckodriverLog Source # | |
Defined in Test.Tasty.WebDriver | |
newtype PrivateMode Source #
Run in private mode.
Constructors
| PrivateMode | |
Fields | |
Instances
| IsOption PrivateMode Source # | |
Defined in Test.Tasty.WebDriver Methods parseValue :: String -> Maybe PrivateMode # optionName :: Tagged PrivateMode String # optionHelp :: Tagged PrivateMode String # showDefaultValue :: PrivateMode -> Maybe String # | |
module Test.Tasty.WebDriver.Config