Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.WebDriver
Description
Once upon a time, the main browser automation tool was Selenium. Users of
this package had to start a Selenium session themselves, making sure to
configure it with a browser-specific driver program like chromedriver
or
geckodriver
, and provide a hostname/port. Then, this package would connect to
Selenium and use its wire protocol to control browsers.
Nowadays, there is an official W3C spec (https://www.w3.org/TR/webdriver1) specifying the protocol, and a number of implementations. Selenium still exists, but Chromedriver and Geckodriver can both serve as standalone WebDriver servers. This library now helps you start up a driver in one of these supported configurations:
- Selenium.jar with one or more supported sub-drivers (
chromedriver
,geckodriver
). This is similar to the traditional picture. - Chromedriver standalone.
- Geckodriver standalone.
You can pick the configuration you want by passing a DriverConfig
to the
startSession
function. The WebDriver implementations have a few differences
between them, which this library tries to smooth over. For example, a single
Geckodriver instance can't start multiple Firefox sessions (see
https://github.com/mozilla/geckodriver/issues/1946). So, this library will spin
up a separate geckodriver
process for every session.
Synopsis
- data WebDriverContext
- mkEmptyWebDriverContext :: MonadIO m => m WebDriverContext
- teardownWebDriverContext :: (WebDriverBase m, MonadLogger m) => WebDriverContext -> m ()
- startSession :: (WebDriverBase m, MonadMask m, MonadLogger m) => WebDriverContext -> DriverConfig -> Capabilities -> String -> m Session
- closeSession :: (WebDriverBase m, MonadLogger m) => WebDriverContext -> Session -> m ()
- data DriverConfig
- = DriverConfigSeleniumJar { }
- | DriverConfigGeckodriver { }
- | DriverConfigChromedriver { }
- startSession' :: (WebDriverBase m, MonadLogger m) => Driver -> Capabilities -> String -> m Session
- closeSession' :: (WebDriverBase m, MonadLogger m) => Session -> m ()
- mkManualDriver :: MonadIO m => String -> Int -> String -> RequestHeaders -> m Driver
- defaultCaps :: Capabilities
- defaultChromeOptions :: ChromeOptions
- defaultFirefoxOptions :: FirefoxOptions
- data Capabilities = Capabilities {
- _capabilitiesBrowserName :: Maybe String
- _capabilitiesBrowserVersion :: Maybe String
- _capabilitiesPlatformName :: Maybe Platform
- _capabilitiesAcceptInsecureCerts :: Maybe Bool
- _capabilitiesPageLoadStrategy :: Maybe String
- _capabilitiesProxy :: Maybe Proxy
- _capabilitiesSetWindowRect :: Maybe Bool
- _capabilitiesTimeouts :: Maybe Timeouts
- _capabilitiesUnhandledPromptBehavior :: Maybe UserPromptHandler
- _capabilitiesGoogChromeOptions :: Maybe ChromeOptions
- _capabilitiesMozFirefoxOptions :: Maybe FirefoxOptions
- _capabilitiesWebSocketUrl :: Maybe Bool
- data Platform
- data ProxyType
- module Test.WebDriver.Commands
- mkDriverRequest :: ToJSON a => Driver -> Method -> Text -> a -> Request
- _driverManager :: Driver -> Manager
- type WebDriver (m :: Type -> Type) = (WebDriverBase m, SessionState m)
- class MonadUnliftIO m => WebDriverBase (m :: Type -> Type)
- data Session
- data FailedCommandError
- = ElementClickIntercepted
- | ElementNotInteractable
- | InsecureCertificate
- | InvalidArgument
- | InvalidCookieDomain
- | InvalidElementState
- | InvalidSelector
- | InvalidSessionId
- | JavascriptError
- | MoveTargetOutOfBounds
- | NoSuchAlert
- | NoSuchCookie
- | NoSuchElement
- | NoSuchFrame
- | NoSuchWindow
- | ScriptTimeout
- | SessionNotCreated
- | StaleElementReference
- | Timeout
- | UnableToSetCookie
- | UnableToCaptureScreen
- | UnexpectedAlertOpen
- | UnknownCommand
- | UnknownError
- | UnknownMethod
- | UnsupportedOperation
- | UnparsedError Text
- data StackFrame = StackFrame {}
- newtype InvalidURL = InvalidURL String
- data NoSessionId = NoSessionId String CallStack
- newtype BadJSON = BadJSON String
- data HTTPStatusUnknown = HTTPStatusUnknown Int String
- newtype ServerError = ServerError String
- data FailedCommand = FailedCommand {}
WebDriverContext
data WebDriverContext Source #
The WebDriverContext
is an opaque type used by this library for
bookkeeping purposes. It tracks all the processes we spin up and all the
sessions we create.
Currently, we will create at most 1 Selenium or Chromedriver process per
WebDriverContext
, and N Geckodriver processes, where N is the number of
Firefox sessions you request.
mkEmptyWebDriverContext :: MonadIO m => m WebDriverContext Source #
Create a new WebDriverContext
.
teardownWebDriverContext :: (WebDriverBase m, MonadLogger m) => WebDriverContext -> m () Source #
Tear down all sessions and processes associated with a WebDriverContext
.
Managed sessions
startSession :: (WebDriverBase m, MonadMask m, MonadLogger m) => WebDriverContext -> DriverConfig -> Capabilities -> String -> m Session Source #
Start a WebDriver session, with a given WebDriverContext
and
DriverConfig
.
You need to provide the WebDriver Capabilities
for the session. You should
make sure the browser-specific fields of your Capabilities
are filled in
correctly to match the given DriverConfig
. For example, if you're using
DriverConfigChromedriver
, you should make sure to fill in
_capabilitiesGoogChromeOptions
and in particular the _chromeOptionsBinary
field.
closeSession :: (WebDriverBase m, MonadLogger m) => WebDriverContext -> Session -> m () Source #
Close the given WebDriver session. This sends the DELETE
/session/:sessionId
command to the WebDriver API, and then shuts down the
process if necessary.
data DriverConfig Source #
Configuration for how to launch a given driver.
Constructors
DriverConfigSeleniumJar | For launching a WebDriver via "java -jar selenium.jar".
Selenium can launch other drivers on your behalf. You should pass these as |
Fields
| |
DriverConfigGeckodriver | |
Fields
| |
DriverConfigChromedriver | |
Fields
|
Lower-level session management
startSession' :: (WebDriverBase m, MonadLogger m) => Driver -> Capabilities -> String -> m Session Source #
Lower-level version of startSession
. This one allows you to construct a
driver instance manually and pass it in. Does not manage process lifecycles.
closeSession' :: (WebDriverBase m, MonadLogger m) => Session -> m () Source #
Close the given WebDriver session. This is a lower-level version of
closeSession
, which manages the driver lifecycle for you. This version will
only issue the DELETE /session/:sessionId
command to the driver, but will
not shut driver processes.
Arguments
:: MonadIO m | |
=> String | Host name |
-> Int | Port |
-> String | Base HTTP path (use "/wd/hub" for Selenium) |
-> RequestHeaders | Headers to send with every request |
-> m Driver |
Create a manual Driver
to use with startSession'
/closeSession'
.
Capabilities
defaultCaps :: Capabilities Source #
Default capabilities.
data Capabilities Source #
A structure describing the capabilities of a session. This record serves dual roles.
It's used to specify the desired capabilities for a session before it's created. In this usage, fields that are set to Nothing indicate that we have no preference for that capability.
When received from the server , it's used to describe the actual capabilities given to us by the WebDriver server. Here a value of Nothing indicates that the server doesn't support the capability. Thus, for Maybe Bool fields, both Nothing and Just False indicate a lack of support for the desired capability.
Constructors
Capabilities | |
Fields
|
Instances
FromJSON Capabilities Source # | |
Defined in Test.WebDriver.Capabilities | |
ToJSON Capabilities Source # | |
Defined in Test.WebDriver.Capabilities Methods toJSON :: Capabilities -> Value # toEncoding :: Capabilities -> Encoding # toJSONList :: [Capabilities] -> Value # toEncodingList :: [Capabilities] -> Encoding # omitField :: Capabilities -> Bool # | |
Show Capabilities Source # | |
Defined in Test.WebDriver.Capabilities Methods showsPrec :: Int -> Capabilities -> ShowS # show :: Capabilities -> String # showList :: [Capabilities] -> ShowS # | |
Eq Capabilities Source # | |
Defined in Test.WebDriver.Capabilities |
Represents the platformName option of the primary capabilities
Commands
module Test.WebDriver.Commands
_driverManager :: Driver -> Manager Source #
WebDriver monad
type WebDriver (m :: Type -> Type) = (WebDriverBase m, SessionState m) Source #
class MonadUnliftIO m => WebDriverBase (m :: Type -> Type) Source #
A class for monads that can handle wire protocol requests. This is the operation underlying all of the high-level commands exported in Test.WebDriver.Commands.
Minimal complete definition
Exceptions
data FailedCommandError Source #
Constructors
ElementClickIntercepted | The Element Click command could not be completed because the element receiving the events is obscuring the element that was requested clicked. |
ElementNotInteractable | A command could not be completed because the element is not pointer- or keyboard interactable. |
InsecureCertificate | Navigation caused the user agent to hit a certificate warning, which is usually the result of an expired or invalid TLS certificate. |
InvalidArgument | The arguments passed to a command are either invalid or malformed. |
InvalidCookieDomain | An illegal attempt was made to set a cookie under a different domain than the current page. |
InvalidElementState | A command could not be completed because the element is in an invalid state, e.g. attempting to clear an element that isn't both editable and resettable. |
InvalidSelector | Argument was an invalid selector. |
InvalidSessionId | Occurs if the given session id is not in the list of active sessions, meaning the session either does not exist or that it’s not active. |
JavascriptError | An error occurred while executing JavaScript supplied by the user. |
MoveTargetOutOfBounds | The target for mouse interaction is not in the browser’s viewport and cannot be brought into that viewport. |
NoSuchAlert | An attempt was made to operate on a modal dialog when one was not open. |
NoSuchCookie | No cookie matching the given path name was found amongst the associated cookies of the current browsing context’s active document. |
NoSuchElement | An element could not be located on the page using the given search parameters. |
NoSuchFrame | A command to switch to a frame could not be satisfied because the frame could not be found. |
NoSuchWindow | A command to switch to a window could not be satisfied because the window could not be found. |
ScriptTimeout | A script did not complete before its timeout expired. |
SessionNotCreated | A new session could not be created. |
StaleElementReference | A command failed because the referenced element is no longer attached to the DOM. |
Timeout | An operation did not complete before its timeout expired. |
UnableToSetCookie | A command to set a cookie’s value could not be satisfied. |
UnableToCaptureScreen | A screen capture was made impossible. |
UnexpectedAlertOpen | A modal dialog was open, blocking this operation. |
UnknownCommand | A command could not be executed because the remote end is not aware of it. |
UnknownError | An unknown error occurred in the remote end while processing the command. |
UnknownMethod | The requested command matched a known URL but did not match an method for that URL. |
UnsupportedOperation | Indicates that a command that should have executed properly cannot be supported for some reason. |
UnparsedError Text | Some error string we weren't able to parse. |
Instances
FromJSON FailedCommandError Source # | |
Defined in Test.WebDriver.Exceptions Methods parseJSON :: Value -> Parser FailedCommandError # parseJSONList :: Value -> Parser [FailedCommandError] # | |
ToJSON FailedCommandError Source # | |
Defined in Test.WebDriver.Exceptions Methods toJSON :: FailedCommandError -> Value # toEncoding :: FailedCommandError -> Encoding # toJSONList :: [FailedCommandError] -> Value # toEncodingList :: [FailedCommandError] -> Encoding # omitField :: FailedCommandError -> Bool # | |
Show FailedCommandError Source # | |
Defined in Test.WebDriver.Exceptions Methods showsPrec :: Int -> FailedCommandError -> ShowS # show :: FailedCommandError -> String # showList :: [FailedCommandError] -> ShowS # | |
Eq FailedCommandError Source # | |
Defined in Test.WebDriver.Exceptions Methods (==) :: FailedCommandError -> FailedCommandError -> Bool # (/=) :: FailedCommandError -> FailedCommandError -> Bool # |
data StackFrame Source #
An individual stack frame from the stack trace provided by the server during a FailedCommand.
Constructors
StackFrame | |
Fields
|
Instances
FromJSON StackFrame Source # | |
Defined in Test.WebDriver.Types | |
Show StackFrame Source # | |
Defined in Test.WebDriver.Types Methods showsPrec :: Int -> StackFrame -> ShowS # show :: StackFrame -> String # showList :: [StackFrame] -> ShowS # | |
Eq StackFrame Source # | |
Defined in Test.WebDriver.Types |
newtype InvalidURL Source #
An invalid URL was given
Constructors
InvalidURL String |
Instances
Exception InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions Methods toException :: InvalidURL -> SomeException # fromException :: SomeException -> Maybe InvalidURL # displayException :: InvalidURL -> String # | |
Show InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions Methods showsPrec :: Int -> InvalidURL -> ShowS # show :: InvalidURL -> String # showList :: [InvalidURL] -> ShowS # | |
Eq InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions |
data NoSessionId Source #
A command requiring a session ID was attempted when no session ID was available.
Constructors
NoSessionId String CallStack |
Instances
Exception NoSessionId Source # | |
Defined in Test.WebDriver.Exceptions Methods toException :: NoSessionId -> SomeException # fromException :: SomeException -> Maybe NoSessionId # displayException :: NoSessionId -> String # | |
Show NoSessionId Source # | |
Defined in Test.WebDriver.Exceptions Methods showsPrec :: Int -> NoSessionId -> ShowS # show :: NoSessionId -> String # showList :: [NoSessionId] -> ShowS # |
An error occured when parsing a JSON value.
Instances
Exception BadJSON Source # | |
Defined in Test.WebDriver.JSON Methods toException :: BadJSON -> SomeException # fromException :: SomeException -> Maybe BadJSON # displayException :: BadJSON -> String # | |
Show BadJSON Source # | |
Eq BadJSON Source # | |
data HTTPStatusUnknown Source #
An unexpected HTTP status was sent by the server.
Constructors
HTTPStatusUnknown Int String |
Instances
Exception HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions Methods toException :: HTTPStatusUnknown -> SomeException # | |
Show HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions Methods showsPrec :: Int -> HTTPStatusUnknown -> ShowS # show :: HTTPStatusUnknown -> String # showList :: [HTTPStatusUnknown] -> ShowS # | |
Eq HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions Methods (==) :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool # (/=) :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool # |
newtype ServerError Source #
An unidentified server-side exception occured
Constructors
ServerError String |
Instances
Exception ServerError Source # | |
Defined in Test.WebDriver.Exceptions Methods toException :: ServerError -> SomeException # fromException :: SomeException -> Maybe ServerError # displayException :: ServerError -> String # | |
Show ServerError Source # | |
Defined in Test.WebDriver.Exceptions Methods showsPrec :: Int -> ServerError -> ShowS # show :: ServerError -> String # showList :: [ServerError] -> ShowS # | |
Eq ServerError Source # | |
Defined in Test.WebDriver.Exceptions |
data FailedCommand Source #
Internal type representing the JSON response object.
Constructors
FailedCommand | |
Fields
|
Instances
FromJSON FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions Methods parseJSON :: Value -> Parser FailedCommand # parseJSONList :: Value -> Parser [FailedCommand] # | |
Exception FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions Methods toException :: FailedCommand -> SomeException # fromException :: SomeException -> Maybe FailedCommand # displayException :: FailedCommand -> String # | |
Show FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions Methods showsPrec :: Int -> FailedCommand -> ShowS # show :: FailedCommand -> String # showList :: [FailedCommand] -> ShowS # | |
Eq FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions Methods (==) :: FailedCommand -> FailedCommand -> Bool # (/=) :: FailedCommand -> FailedCommand -> Bool # |