webdriver-precore
Safe HaskellNone
LanguageHaskell2010

WebDriverPreCore

Synopsis

Introduction

What is This Library?

This library provides a minimal abstraction over the WebDriver W3C Protocol endpoints without providing any implementation. It provides a description of the W3C API as a list of functions returning a W3Spec. The intention is that other libraries will provide the actual implementation.

You can not use this library directly to drive a browser. If you are looking for a library to drive a browser, you may be interested in an alternative library such haskell-webdriver.

Why This Library?

There are a number of libraries that provide WebDriver bindings for Haskell. However, at the time work on this library commenced the available libraries were either in need of maintenance, required Selenium, or part of larger opinionated testing frameworks.

The goal of the authors of this library is to enable browser interaction in our own high level testing framework. We would prefer to communicate with drivers directly, using the W3C standards (developed largely by the Selenium core contributors) rather than depend on Selenium itself. We would also like to avoid pulling in too many dependencies or potentially incompatible concepts from other high level libraries. To achieve this, we plan to first develop a number of unopinionated, lower level libraries that can be used by others without buying into our entire stack.

This library is the first of those libraries, and is intended to provide a low-dependency base on which fully featured (W3C) WebDriver libraries can be built.

Implementing WebDriver Interaction

Using webdriver-precore to build a webdriver library requires two steps to attain the basic functionality provided by the WebDriver API:

  1. Implement a runner (run function) that, given a W3Spec, can make HTTP requests to the WebDriver server and parse the response.
  2. Apply the runner to the W3Spec functions provided by this library to transform the W3Spec into actual IO browser interactions (this is just boilerplate).

1. Implementing a runner

This is an example of a minimal runner that implements the interaction with WebDriver endpoint definitions as provided by this library.

The first step in writing a WebDriver implementation is to choose an HTTP library. In this example we have chosen req.

Then to implement a run function requires the following:

  1. Define a function to transform a W3Spec to RequestParams compatible with the chosen HTTP library.
  2. Make an HTTP call to WebDriver as per the RequestParams and return a simplified HttpResponse.
  3. Use the parser provided by the W3Spec to transform the HttpResponse to the desired result type and handle any errors.

Example

The full source for this example can be found in the project repo.

Module Header

Expand
  {-# LANGUAGE DataKinds #-}
  {-# LANGUAGE DuplicateRecordFields #-}
  {-# LANGUAGE ExistentialQuantification #-}
  {-# LANGUAGE GADTs #-}
  {-# LANGUAGE LambdaCase #-}
  {-# LANGUAGE NamedFieldPuns #-}
  {-# LANGUAGE NoImplicitPrelude #-}
  {-# LANGUAGE OverloadedRecordDot #-}
  {-# LANGUAGE OverloadedStrings #-}
  {-# LANGUAGE NoFieldSelectors #-}
  module IORunnerMinimal ( run ) where
  import Data.Aeson (Result (..), Value, object)
  import Data.Function ((&), ($), (.))
  import Data.Text  as T (Text, unpack)
  import Data.Text.Encoding (decodeUtf8Lenient)
  import WebDriverPreCore (
    HttpResponse (..),
    W3Spec (..),
    parseWebDriverError,
    ErrorClassification (..),
    UrlPath (..) )
  import GHC.IO (IO)
  import Data.Int (Int)
  import Control.Monad (Monad(..))
  import Data.Foldable (foldl')
  import GHC.Maybe (Maybe(..))
  import Control.Applicative (Applicative(..))
  import Control.Monad.Fail (MonadFail(..))
  import Data.Monoid ((<>))
  import GHC.Show (Show(..))
  import Network.HTTP.Req as R
    ( DELETE (DELETE),
      GET (GET),
      NoReqBody (NoReqBody),
      POST (POST),
      ReqBodyJson (ReqBodyJson),
      JsonResponse,
      defaultHttpConfig,
      http,
      jsonResponse,
      port,
      req,
      responseBody,
      responseStatusCode,
      responseStatusMessage,
      runReq,
      HttpConfig (httpConfigCheckResponse), (/:), HttpBodyAllowed, HttpMethod (..), ProvidesBody, HttpBody, Url, Scheme (..),
    )

run function

run :: W3Spec a -> IO a
run spec = do
  let request = mkRequest spec -- 1. Convert W3Spec to params for req
  response <- callReq request  -- 2. Call WebDriver server (via req) and return a simplified HttpResponse
  parseResponse spec response  -- 3. Use the W3Spec parser to convert the HttpResponse to the desired result type and handle any errors

1.1 W3Spec -> ReqRequestParams

Transform W3Spec to ReqRequestParams

-- ReqRequestParams are specific to the chosen HTTP library (in this example req)
-- The port would not normally be hard coded

mkRequest :: forall a. W3Spec a -> ReqRequestParams
mkRequest spec = case spec of
  Get {} -> MkRequestParams url GET NoReqBody 4444
  Post {body} -> MkRequestParams url POST (ReqBodyJson body) 4444
  PostEmpty {} -> MkRequestParams url POST (ReqBodyJson $ object []) 4444
  Delete {} -> MkRequestParams url DELETE NoReqBody 4444
  where
    url =  foldl' (/:) (http "127.0.0.1") spec.path.segments

-- A custom data type for request params specific to req

data ReqRequestParams where
  MkRequestParams ::
    (HttpBodyAllowed (AllowsBody method) (ProvidesBody body), HttpMethod method, HttpBody body) =>
    { url :: Url 'Http,
      method :: method,
      body :: body,
      port :: Int
    } ->
    ReqRequestParams

1.2 Call the WebDriver

Call WebDriver endpoints based on ReqRequestParams

callReq :: ReqRequestParams -> IO HttpResponse
callReq MkRequestParams {url, method, body, port = prt} =
  runReq defaultHttpConfig {httpConfigCheckResponse = \_ _ _ -> Nothing} $ do
    r <- req method url body jsonResponse $ port prt
    pure $
      MkHttpResponse
        { statusCode = responseStatusCode r,
          statusMessage = responseStatusText r,
          body = responseBody r :: Value
        }
  where
    responseStatusText = decodeUtf8Lenient . responseStatusMessage

1.3 Parse HttpResponse using the parser provided by W3Spec

Parse the WebDriver response (in this implimentation we are just throwing exceptions on failure)

parseResponse :: W3Spec a -> HttpResponse -> IO a
parseResponse spec r =
  spec.parser r
    & \case
      Error msg -> fail $ parseWebDriverError r & case
          e@NotAnError {} -> unpack spec.description <> "\n" <> "Failed to parse response:\n " <> msg <> "\nin response:" <> show e
          e@UnrecognisedError {} -> "UnrecognisedError:\n " <> "\nin response:" <> show e
          e@WebDriverError {} -> "WebDriver error thrown:\n " <> show e
      Success a -> pure a

2. Applying the runner to the W3Spec functions

Create an IO API by applying run to each endpoint definition exposed by this library

Full source can be found in the project repo

module IOAPI where 

import WebDriverPreCore qualified as W

status :: IO DriverStatus
status = run W.status

newSession :: W.FullCapabilities -> IO SessionId
newSession = run . W.newSession

getTimeouts :: SessionId -> IO W.Timeouts
getTimeouts = run . W.getTimeouts

setTimeouts :: SessionId -> W.Timeouts -> IO ()
setTimeouts s = run . W.setTimeouts s

getCurrentUrl :: SessionId -> IO Text
getCurrentUrl = run . W.getCurrentUrl

getTitle :: SessionId -> IO Text
getTitle = run . W.getTitle

maximizeWindow :: SessionId -> IO W.WindowRect
maximizeWindow = run . W.maximizeWindow

-- ... and 50+ more API functions

Using the API

Once all the required endpoints are implemented you will be able to interact with browsers via WebDriver

Prerequisites:

  1. An appropriate browser and WebDriver installed.
  2. WebDriver started.

e.g. For Firefox and geckodriver on Linux or WSL you could start geckodriver from the terminal as follows: Note: we are setting the port to 4444, which is the hard coded port in our example.

>>> pkill -f geckodriver || true  && geckodriver --port=4444 &

or with logging:

>>> pkill -f geckodriver || true  && geckodriver --log trace --port=4444 &

or similarly for Chrome and chromedriver:

>>> pkill -f chromedriver || true && chromedriver --port=4444 &

or with logging:

>>> pkill -f chromedriver || true && chromedriver --log-level=ALL --port=4444 &

With the driver running you can now interact with the browser:

Example: A full example source file can be found in the project repo.

demoForwardBackRefresh :: IO ()
demoForwardBackRefresh = do
  ses <- newSession $ minFullCapabilities Firefox
  navigateTo ses "https://the-internet.herokuapp.com/"
  link findElement ses $ CSS "#content ul:nth-child(4) > li:nth-child(6) > a:nth-child(1)"
  elementClick ses link
  back ses
  forward ses
  refresh ses
  deleteSession ses

Note this is a minimal API. There is plenty of scope to build on this to provide a more user-friendly functions.

The API

The W3Spec Type

data W3Spec a Source #

The W3Spec type is a specification for a WebDriver command. Every endpoint function in this module returns a W3Spec object.

Instances

Instances details
Show a => Show (W3Spec a) Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Methods

showsPrec :: Int -> W3Spec a -> ShowS #

show :: W3Spec a -> String #

showList :: [W3Spec a] -> ShowS #

Root Methods

newSession :: FullCapabilities -> W3Spec SessionId Source #

Return a spec to create a new session given FullCapabilities object.

newSession' can be used if FullCapabilities doesn't meet your requirements.

spec

POST 	/session 	New Session

newSession' :: ToJSON a => a -> W3Spec SessionId Source #

Return a spec to create a new session given an object of any type that implements ToJSON.

The FullCapabilities type and associated types should work for the vast majority use cases, but if the required capabilities are not covered by the types provided, newSession'. can be used with a custom type instead. newSession' works with any type that implements ToJSON, (including an Aeson Value).

Obviously, any type used must produce a JSON object compatible with capabilities as defined W3C spec.

spec

POST 	/session 	New Session

status :: W3Spec DriverStatus Source #

Return a spec to get the status of the driver.

spec

GET 	/status 	Status

Session Methods

See also newSession and newSession'

acceptAlert :: SessionId -> W3Spec () Source #

Return a spec to accept an alert on the current page given a SessionId.

spec

POST 	/session/{session id}/alert/accept 	Accept Alert

addCookie :: SessionId -> Cookie -> W3Spec () Source #

Return a spec to add a cookie to the current page given a SessionId and Cookie.

spec

POST 	/session/{session id}/cookie 	Add Cookie

back :: SessionId -> W3Spec () Source #

Return a spec to navigate back in the browser history given a SessionId.

spec

POST 	/session/{session id}/back 	Back

closeWindow :: SessionId -> W3Spec () Source #

Return a spec to close the current window given a SessionId.

spec

DELETE 	/session/{session id}/window 	Close Window

deleteAllCookies :: SessionId -> W3Spec () Source #

Return a spec to delete all cookies from the current page given a SessionId.

spec

DELETE 	/session/{session id}/cookie 	Delete All Cookies

deleteCookie :: SessionId -> Text -> W3Spec () Source #

Return a spec to delete a named cookie from the current page given a SessionId and cookie name.

spec

DELETE 	/session/{session id}/cookie/{name} 	Delete Cookie

deleteSession :: SessionId -> W3Spec () Source #

Return a spec to delete a session given a SessionId.

spec

DELETE 	/session/{session id} 	Delete Session

dismissAlert :: SessionId -> W3Spec () Source #

Return a spec to dismiss an alert on the current page given a SessionId.

spec

POST 	/session/{session id}/alert/dismiss 	Dismiss Alert

executeScript :: SessionId -> Text -> [Value] -> W3Spec Value Source #

Return a spec to execute a script in the context of the current page given a SessionId, Text script, and a list of Value arguments.

spec

POST 	/session/{session id}/execute/sync 	Execute Script

executeScriptAsync :: SessionId -> Text -> [Value] -> W3Spec Value Source #

Return a spec to execute an asynchronous script in the context of the current page given a SessionId, Text script, and a list of Value arguments.

spec

POST 	/session/{session id}/execute/async 	Execute Async Script

forward :: SessionId -> W3Spec () Source #

Return a spec to navigate forward in the browser history given a SessionId.

spec

POST 	/session/{session id}/forward 	Forward

fullscreenWindow :: SessionId -> W3Spec WindowRect Source #

Return a spec to fullscreen the current window given a SessionId.

spec

POST 	/session/{session id}/window/fullscreen 	Fullscreen Window

getAlertText :: SessionId -> W3Spec Text Source #

Return a spec to get the text of an alert on the current page given a SessionId.

spec

GET 	/session/{session id}/alert/text 	Get Alert Text

getAllCookies :: SessionId -> W3Spec [Cookie] Source #

Return a spec to get all cookies of the current page given a SessionId.

spec

GET 	/session/{session id}/cookie 	Get All Cookies

getCurrentUrl :: SessionId -> W3Spec Text Source #

Return a spec to get the current URL of a session given a SessionId.

spec

GET 	/session/{session id}/url 	Get Current URL

getNamedCookie :: SessionId -> Text -> W3Spec Cookie Source #

Return a spec to get a named cookie of the current page given a SessionId and cookie name.

spec

GET 	/session/{session id}/cookie/{name} 	Get Named Cookie

getPageSource :: SessionId -> W3Spec Text Source #

Return a spec to get the source of the current page given a SessionId.

spec

GET 	/session/{session id}/source 	Get Page Source

getTimeouts :: SessionId -> W3Spec Timeouts Source #

Return a spec to get the timeouts of a session given a SessionId.

spec

GET 	/session/{session id}/timeouts 	Get Timeouts

getTitle :: SessionId -> W3Spec Text Source #

Return a spec to get the title of the current page given a SessionId.

spec

GET 	/session/{session id}/title 	Get Title

getWindowHandle :: SessionId -> W3Spec WindowHandle Source #

Return a spec to get the current window handle given a SessionId.

spec

GET 	/session/{session id}/window 	Get Window Handle

getWindowHandles :: SessionId -> W3Spec [WindowHandle] Source #

Return a spec to get all window handles of the current session given a SessionId.

spec

GET 	/session/{session id}/window/handles 	Get Window Handles

getWindowRect :: SessionId -> W3Spec WindowRect Source #

Return a spec to get the window rect of the current window given a SessionId.

spec

GET 	/session/{session id}/window/rect 	Get Window Rect

maximizeWindow :: SessionId -> W3Spec WindowRect Source #

Return a spec to maximize the current window given a SessionId.

spec

POST 	/session/{session id}/window/maximize 	Maximize Window

minimizeWindow :: SessionId -> W3Spec WindowRect Source #

Return a spec to minimize the current window given a SessionId.

spec

POST 	/session/{session id}/window/minimize 	Minimize Window

navigateTo :: SessionId -> Text -> W3Spec () Source #

Return a spec to navigate to a URL given a SessionId and a Text URL.

spec

POST 	/session/{session id}/url 	Navigate To

newWindow :: SessionId -> W3Spec WindowHandleSpec Source #

Return a spec to create a new window given a SessionId.

spec

POST 	/session/{session id}/window/new 	New Window

performActions :: SessionId -> Actions -> W3Spec () Source #

Return a spec to perform actions on the current page given a SessionId and Actions.

spec

POST 	/session/{session id}/actions 	Perform Actions

printPage :: SessionId -> W3Spec Text Source #

Return a spec to print the current page given a SessionId.

spec

POST 	/session/{session id}/print 	Print Page

refresh :: SessionId -> W3Spec () Source #

Return a spec to refresh the current page given a SessionId.

spec

POST 	/session/{session id}/refresh 	Refresh

releaseActions :: SessionId -> W3Spec () Source #

Return a spec to release actions on the current page given a SessionId.

spec

DELETE 	/session/{session id}/actions 	Release Actions

sendAlertText :: SessionId -> Text -> W3Spec () Source #

Return a spec to send text to an alert on the current page given a SessionId and Text.

spec

POST 	/session/{session id}/alert/text 	Send Alert Text

setTimeouts :: SessionId -> Timeouts -> W3Spec () Source #

Return a spec to set the timeouts of a session given a SessionId and Timeouts.

spec

POST 	/session/{session id}/timeouts 	Set Timeouts

setWindowRect :: SessionId -> WindowRect -> W3Spec WindowRect Source #

Return a spec to set the window rect of the current window given a SessionId and WindowRect.

spec

POST 	/session/{session id}/window/rect 	Set Window Rect

switchToFrame :: SessionId -> FrameReference -> W3Spec () Source #

Return a spec to switch to a different frame given a SessionId and FrameReference.

spec

POST 	/session/{session id}/frame 	Switch To Frame

switchToWindow :: SessionId -> WindowHandle -> W3Spec () Source #

Return a spec to switch to a different window given a SessionId and WindowHandle.

spec

POST 	/session/{session id}/window 	Switch To Window

takeScreenshot :: SessionId -> W3Spec Text Source #

Return a spec to take a screenshot of the current page given a SessionId.

spec

GET 	/session/{session id}/screenshot 	Take Screenshot

Window Methods

closeWindow :: SessionId -> W3Spec () Source #

Return a spec to close the current window given a SessionId.

spec

DELETE 	/session/{session id}/window 	Close Window

fullscreenWindow :: SessionId -> W3Spec WindowRect Source #

Return a spec to fullscreen the current window given a SessionId.

spec

POST 	/session/{session id}/window/fullscreen 	Fullscreen Window

getWindowHandles :: SessionId -> W3Spec [WindowHandle] Source #

Return a spec to get all window handles of the current session given a SessionId.

spec

GET 	/session/{session id}/window/handles 	Get Window Handles

getWindowRect :: SessionId -> W3Spec WindowRect Source #

Return a spec to get the window rect of the current window given a SessionId.

spec

GET 	/session/{session id}/window/rect 	Get Window Rect

maximizeWindow :: SessionId -> W3Spec WindowRect Source #

Return a spec to maximize the current window given a SessionId.

spec

POST 	/session/{session id}/window/maximize 	Maximize Window

minimizeWindow :: SessionId -> W3Spec WindowRect Source #

Return a spec to minimize the current window given a SessionId.

spec

POST 	/session/{session id}/window/minimize 	Minimize Window

newWindow :: SessionId -> W3Spec WindowHandleSpec Source #

Return a spec to create a new window given a SessionId.

spec

POST 	/session/{session id}/window/new 	New Window

setWindowRect :: SessionId -> WindowRect -> W3Spec WindowRect Source #

Return a spec to set the window rect of the current window given a SessionId and WindowRect.

spec

POST 	/session/{session id}/window/rect 	Set Window Rect

switchToWindow :: SessionId -> WindowHandle -> W3Spec () Source #

Return a spec to switch to a different window given a SessionId and WindowHandle.

spec

POST 	/session/{session id}/window 	Switch To Window

Frame Methods

switchToParentFrame :: SessionId -> W3Spec () Source #

Return a spec to switch to the parent frame given a SessionId.

spec

POST 	/session/{session id}/frame/parent 	Switch To Parent Frame

Element(s) Methods

findElement :: SessionId -> Selector -> W3Spec ElementId Source #

Return a spec to find an element on the current page given a SessionId and Selector.

spec

POST 	/session/{session id}/element 	Find Element

findElements :: SessionId -> Selector -> W3Spec [ElementId] Source #

Return a spec to find elements on the current page given a SessionId and Selector.

spec

POST 	/session/{session id}/elements 	Find Elements

getActiveElement :: SessionId -> W3Spec ElementId Source #

Return a spec to get the active element of the current page given a SessionId.

spec

GET 	/session/{session id}/element/active 	Get Active Element

Element Instance Methods

elementClear :: SessionId -> ElementId -> W3Spec () Source #

Return a spec to clear an element given a SessionId and ElementId.

spec

POST 	/session/{session id}/element/{element id}/clear 	Element Clear

elementClick :: SessionId -> ElementId -> W3Spec () Source #

Return a spec to click an element given a SessionId and ElementId.

spec

POST 	/session/{session id}/element/{element id}/click 	Element Click

elementSendKeys :: SessionId -> ElementId -> Text -> W3Spec () Source #

Return a spec to send keys to an element given a SessionId, ElementId, and keys to send.

spec

POST 	/session/{session id}/element/{element id}/value 	Element Send Keys

findElementFromElement :: SessionId -> ElementId -> Selector -> W3Spec ElementId Source #

Return a spec to find an element from another element given a SessionId, ElementId, and Selector.

spec

POST 	/session/{session id}/element/{element id}/element 	Find Element From Element

findElementsFromElement :: SessionId -> ElementId -> Selector -> W3Spec [ElementId] Source #

Return a spec to find elements from another element given a SessionId, ElementId, and Selector.

spec

POST 	/session/{session id}/element/{element id}/elements 	Find Elements From Element

getElementAttribute :: SessionId -> ElementId -> Text -> W3Spec Text Source #

Return a spec to get an attribute of an element given a SessionId, ElementId, and attribute name.

spec

GET 	/session/{session id}/element/{element id}/attribute/{name} 	Get Element Attribute

getElementComputedLabel :: SessionId -> ElementId -> W3Spec Text Source #

Return a spec to get the computed label of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/computedlabel 	Get Computed Label

getElementComputedRole :: SessionId -> ElementId -> W3Spec Text Source #

Return a spec to get the computed role of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/computedrole 	Get Computed Role

getElementCssValue :: SessionId -> ElementId -> Text -> W3Spec Text Source #

Return a spec to get the CSS value of an element given a SessionId, ElementId, and CSS property name.

spec

GET 	/session/{session id}/element/{element id}/css/{property name} 	Get Element CSS Value

getElementProperty :: SessionId -> ElementId -> Text -> W3Spec Value Source #

Return a spec to get a property of an element given a SessionId, ElementId, and property name.

spec

GET 	/session/{session id}/element/{element id}/property/{name} 	Get Element Property

getElementRect :: SessionId -> ElementId -> W3Spec WindowRect Source #

Return a spec to get the rect of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/rect 	Get Element Rect

getElementShadowRoot :: SessionId -> ElementId -> W3Spec ElementId Source #

Return a spec to get the shadow root of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/shadow 	Get Element Shadow Root

getElementTagName :: SessionId -> ElementId -> W3Spec Text Source #

Return a spec to get the tag name of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/name 	Get Element Tag Name

getElementText :: SessionId -> ElementId -> W3Spec Text Source #

Return a spec to get the text of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/text 	Get Element Text

isElementEnabled :: SessionId -> ElementId -> W3Spec Bool Source #

Return a spec to check if an element is enabled given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/enabled 	Is Element Enabled

isElementSelected :: SessionId -> ElementId -> W3Spec Bool Source #

Return a spec to check if an element is selected given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/selected 	Is Element Selected

takeElementScreenshot :: SessionId -> ElementId -> W3Spec Text Source #

Return a spec to take a screenshot of an element given a SessionId and ElementId.

spec

GET 	/session/{session id}/element/{element id}/screenshot 	Take Element Screenshot

Shadow DOM Methods

findElementFromShadowRoot :: SessionId -> ElementId -> Selector -> W3Spec ElementId Source #

Return a spec to find an element from the shadow root given a SessionId, ElementId, and Selector.

spec

POST 	/session/{session id}/shadow/{shadow id}/element 	Find Element From Shadow Root

findElementsFromShadowRoot :: SessionId -> ElementId -> Selector -> W3Spec [ElementId] Source #

Return a spec to find elements from the shadow root given a SessionId, ElementId, and Selector.

spec

POST 	/session/{session id}/shadow/{shadow id}/elements 	Find Elements From Shadow Root

HTTP Response

data HttpResponse Source #

HttpResponse represents a WebDriver HTTP response.

Constructors

MkHttpResponse 

Fields

Capabilities

data Capabilities Source #

Capabilities define the properties of the session and are passed to the webdriver via fields of the FullCapabilities object.

See spec See also: FullCapabilities and related constructors such as minCapabilities, minFullCapabilities, minFirefoxCapabilities and minChromeCapabilities

Instances

Instances details
FromJSON Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep Capabilities 
Instance details

Defined in WebDriverPreCore.Capabilities

Show Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

data FullCapabilities Source #

FullCapabilities is the object that is passed to webdriver to define the properties of the session via the newSession function. It is a combination of alwaysMatch and firstMatch properties.

See spec

See also: Capabilities and related constructors such as minCapabilities, minFullCapabilities, minFirefoxCapabilities and minChromeCapabilities

Constructors

MkFullCapabilities 

Fields

Instances

Instances details
FromJSON FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep FullCapabilities 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep FullCapabilities = D1 ('MetaData "FullCapabilities" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkFullCapabilities" 'PrefixI 'True) (S1 ('MetaSel ('Just "alwaysMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Capabilities)) :*: S1 ('MetaSel ('Just "firstMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Capabilities])))
Show FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep FullCapabilities = D1 ('MetaData "FullCapabilities" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkFullCapabilities" 'PrefixI 'True) (S1 ('MetaSel ('Just "alwaysMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Capabilities)) :*: S1 ('MetaSel ('Just "firstMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Capabilities])))

data LogLevel Source #

Browser log levels as defined in vendor specs

Constructors

Trace

Most verbose logging

Debug

Debug-level information

Config

Configuration details

Info

General operational logs

Warning

Potential issues

Error

Recoverable errors

Fatal

Critical failures

Off

No logging

Instances

Instances details
FromJSON LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Bounded LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Enum LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep LogLevel 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep LogLevel = D1 ('MetaData "LogLevel" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (((C1 ('MetaCons "Trace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Config" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Warning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fatal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Off" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

Show LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep LogLevel Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep LogLevel = D1 ('MetaData "LogLevel" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (((C1 ('MetaCons "Trace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Config" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Warning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fatal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Off" 'PrefixI 'False) (U1 :: Type -> Type))))

data BrowserName Source #

Instances

Instances details
FromJSON BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Bounded BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Enum BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep BrowserName 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep BrowserName = D1 ('MetaData "BrowserName" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Chrome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Firefox" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Safari" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Edge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InternetExplorer" 'PrefixI 'False) (U1 :: Type -> Type))))
Show BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep BrowserName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep BrowserName = D1 ('MetaData "BrowserName" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Chrome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Firefox" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Safari" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Edge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InternetExplorer" 'PrefixI 'False) (U1 :: Type -> Type))))

data DeviceMetrics Source #

Constructors

MkDeviceMetrics 

Fields

Instances

Instances details
FromJSON DeviceMetrics Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON DeviceMetrics Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic DeviceMetrics Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep DeviceMetrics 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep DeviceMetrics = D1 ('MetaData "DeviceMetrics" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkDeviceMetrics" 'PrefixI 'True) ((S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "pixelRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "touch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))
Show DeviceMetrics Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq DeviceMetrics Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep DeviceMetrics Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep DeviceMetrics = D1 ('MetaData "DeviceMetrics" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkDeviceMetrics" 'PrefixI 'True) ((S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "pixelRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "touch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

data Capabilities Source #

Capabilities define the properties of the session and are passed to the webdriver via fields of the FullCapabilities object.

See spec See also: FullCapabilities and related constructors such as minCapabilities, minFullCapabilities, minFirefoxCapabilities and minChromeCapabilities

Instances

Instances details
FromJSON Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep Capabilities 
Instance details

Defined in WebDriverPreCore.Capabilities

Show Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Capabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

data UnhandledPromptBehavior Source #

Instances

Instances details
FromJSON UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Bounded UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Enum UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep UnhandledPromptBehavior 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep UnhandledPromptBehavior = D1 ('MetaData "UnhandledPromptBehavior" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Dismiss" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Accept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DismissAndNotify" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AcceptAndNotify" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignore" 'PrefixI 'False) (U1 :: Type -> Type))))
Show UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep UnhandledPromptBehavior Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep UnhandledPromptBehavior = D1 ('MetaData "UnhandledPromptBehavior" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Dismiss" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Accept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DismissAndNotify" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AcceptAndNotify" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignore" 'PrefixI 'False) (U1 :: Type -> Type))))

data FullCapabilities Source #

FullCapabilities is the object that is passed to webdriver to define the properties of the session via the newSession function. It is a combination of alwaysMatch and firstMatch properties.

See spec

See also: Capabilities and related constructors such as minCapabilities, minFullCapabilities, minFirefoxCapabilities and minChromeCapabilities

Constructors

MkFullCapabilities 

Fields

Instances

Instances details
FromJSON FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep FullCapabilities 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep FullCapabilities = D1 ('MetaData "FullCapabilities" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkFullCapabilities" 'PrefixI 'True) (S1 ('MetaSel ('Just "alwaysMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Capabilities)) :*: S1 ('MetaSel ('Just "firstMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Capabilities])))
Show FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep FullCapabilities Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep FullCapabilities = D1 ('MetaData "FullCapabilities" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkFullCapabilities" 'PrefixI 'True) (S1 ('MetaSel ('Just "alwaysMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Capabilities)) :*: S1 ('MetaSel ('Just "firstMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Capabilities])))

data Timeouts Source #

Timeouts in milliseconds spec

Constructors

MkTimeouts 

Instances

Instances details
FromJSON Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep Timeouts 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Timeouts = D1 ('MetaData "Timeouts" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkTimeouts" 'PrefixI 'True) (S1 ('MetaSel ('Just "implicit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "pageLoad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)))))

Methods

from :: Timeouts -> Rep Timeouts x #

to :: Rep Timeouts x -> Timeouts #

Show Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Timeouts = D1 ('MetaData "Timeouts" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkTimeouts" 'PrefixI 'True) (S1 ('MetaSel ('Just "implicit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "pageLoad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)))))

data PageLoadStrategy Source #

Constructors

None' 
Eager 
Normal 

Instances

Instances details
FromJSON PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Bounded PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Enum PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep PageLoadStrategy 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PageLoadStrategy = D1 ('MetaData "PageLoadStrategy" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "None'" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eager" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Normal" 'PrefixI 'False) (U1 :: Type -> Type)))
Show PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PageLoadStrategy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PageLoadStrategy = D1 ('MetaData "PageLoadStrategy" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "None'" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eager" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Normal" 'PrefixI 'False) (U1 :: Type -> Type)))

data PlatformName Source #

Constructors

Windows 
Mac 
Linux 
Android 
IOS 

Instances

Instances details
FromJSON PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Bounded PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Enum PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep PlatformName 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PlatformName = D1 ('MetaData "PlatformName" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Windows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mac" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Linux" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Android" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IOS" 'PrefixI 'False) (U1 :: Type -> Type))))
Show PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PlatformName Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PlatformName = D1 ('MetaData "PlatformName" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Windows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mac" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Linux" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Android" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IOS" 'PrefixI 'False) (U1 :: Type -> Type))))

data VendorSpecific Source #

Instances

Instances details
ToJSON VendorSpecific Source #

ToJSON Instance for VendorSpecific

Instance details

Defined in WebDriverPreCore.Capabilities

Generic VendorSpecific Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep VendorSpecific 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep VendorSpecific = D1 ('MetaData "VendorSpecific" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "ChromeOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "chromeArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 ('MetaSel ('Just "chromeBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chromeExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "chromeLocalState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value))) :*: (S1 ('MetaSel ('Just "chromeMobileEmulation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MobileEmulation)) :*: S1 ('MetaSel ('Just "chromePrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value)))))) :*: ((S1 ('MetaSel ('Just "chromeDetach") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "chromeDebuggerAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chromeExcludeSwitches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "chromeMinidumpPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "chromePerfLoggingPrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PerfLoggingPrefs)) :*: S1 ('MetaSel ('Just "chromeWindowTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))))) :+: C1 ('MetaCons "EdgeOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "edgeArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 ('MetaSel ('Just "edgeBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "edgeExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "edgeLocalState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value))) :*: (S1 ('MetaSel ('Just "edgeMobileEmulation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MobileEmulation)) :*: S1 ('MetaSel ('Just "edgePrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value)))))) :*: ((S1 ('MetaSel ('Just "edgeDetach") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "edgeDebuggerAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "edgeExcludeSwitches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "edgeMinidumpPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "edgePerfLoggingPrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PerfLoggingPrefs)) :*: S1 ('MetaSel ('Just "edgeWindowTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text]))))))) :+: (C1 ('MetaCons "FirefoxOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "firefoxArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "firefoxBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "firefoxProfile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "firefoxLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogSettings)))) :+: C1 ('MetaCons "SafariOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "safariAutomaticInspection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "safariAutomaticProfiling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)))))
Show VendorSpecific Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq VendorSpecific Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep VendorSpecific Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep VendorSpecific = D1 ('MetaData "VendorSpecific" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "ChromeOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "chromeArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 ('MetaSel ('Just "chromeBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chromeExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "chromeLocalState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value))) :*: (S1 ('MetaSel ('Just "chromeMobileEmulation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MobileEmulation)) :*: S1 ('MetaSel ('Just "chromePrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value)))))) :*: ((S1 ('MetaSel ('Just "chromeDetach") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "chromeDebuggerAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chromeExcludeSwitches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "chromeMinidumpPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "chromePerfLoggingPrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PerfLoggingPrefs)) :*: S1 ('MetaSel ('Just "chromeWindowTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))))) :+: C1 ('MetaCons "EdgeOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "edgeArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 ('MetaSel ('Just "edgeBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "edgeExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "edgeLocalState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value))) :*: (S1 ('MetaSel ('Just "edgeMobileEmulation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MobileEmulation)) :*: S1 ('MetaSel ('Just "edgePrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Map Text Value)))))) :*: ((S1 ('MetaSel ('Just "edgeDetach") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "edgeDebuggerAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "edgeExcludeSwitches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])))) :*: (S1 ('MetaSel ('Just "edgeMinidumpPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "edgePerfLoggingPrefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PerfLoggingPrefs)) :*: S1 ('MetaSel ('Just "edgeWindowTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text]))))))) :+: (C1 ('MetaCons "FirefoxOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "firefoxArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "firefoxBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "firefoxProfile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "firefoxLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogSettings)))) :+: C1 ('MetaCons "SafariOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "safariAutomaticInspection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "safariAutomaticProfiling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)))))

data SocksProxy Source #

Constructors

MkSocksProxy 

Instances

Instances details
FromJSON SocksProxy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON SocksProxy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic SocksProxy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep SocksProxy 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep SocksProxy = D1 ('MetaData "SocksProxy" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkSocksProxy" 'PrefixI 'True) (S1 ('MetaSel ('Just "socksProxy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "socksVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))
Show SocksProxy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq SocksProxy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep SocksProxy Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep SocksProxy = D1 ('MetaData "SocksProxy" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkSocksProxy" 'PrefixI 'True) (S1 ('MetaSel ('Just "socksProxy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "socksVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))

data PerfLoggingPrefs Source #

Instances

Instances details
FromJSON PerfLoggingPrefs Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON PerfLoggingPrefs Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic PerfLoggingPrefs Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep PerfLoggingPrefs 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PerfLoggingPrefs = D1 ('MetaData "PerfLoggingPrefs" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkPerfLoggingPrefs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "enableNetwork") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "enablePage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "enableTimeline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "traceCategories") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "bufferUsageReportingInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int))))))
Show PerfLoggingPrefs Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq PerfLoggingPrefs Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PerfLoggingPrefs Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep PerfLoggingPrefs = D1 ('MetaData "PerfLoggingPrefs" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkPerfLoggingPrefs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "enableNetwork") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "enablePage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "enableTimeline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "traceCategories") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "bufferUsageReportingInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int))))))

data MobileEmulation Source #

Instances

Instances details
FromJSON MobileEmulation Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON MobileEmulation Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic MobileEmulation Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep MobileEmulation 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep MobileEmulation = D1 ('MetaData "MobileEmulation" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkMobileEmulation" 'PrefixI 'True) (S1 ('MetaSel ('Just "deviceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "deviceMetrics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DeviceMetrics)) :*: S1 ('MetaSel ('Just "userAgent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)))))
Show MobileEmulation Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq MobileEmulation Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep MobileEmulation Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep MobileEmulation = D1 ('MetaData "MobileEmulation" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkMobileEmulation" 'PrefixI 'True) (S1 ('MetaSel ('Just "deviceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "deviceMetrics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DeviceMetrics)) :*: S1 ('MetaSel ('Just "userAgent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)))))

data LogSettings Source #

Log settings structure for vendor capabilities

Constructors

MkLogSettings 

Fields

Instances

Instances details
FromJSON LogSettings Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON LogSettings Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic LogSettings Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep LogSettings 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep LogSettings = D1 ('MetaData "LogSettings" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkLogSettings" 'PrefixI 'True) (S1 ('MetaSel ('Just "level") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LogLevel)))
Show LogSettings Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq LogSettings Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep LogSettings Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep LogSettings = D1 ('MetaData "LogSettings" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkLogSettings" 'PrefixI 'True) (S1 ('MetaSel ('Just "level") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LogLevel)))

minCapabilities :: BrowserName -> Capabilities Source #

Returns the minimal Capabilities object for a given browser The browserName is the only field populated See spec

minFullCapabilities :: BrowserName -> FullCapabilities Source #

Returns the minimal FullCapabilities object for a given browser The browserName in the alwaysMatch field is the only field populated See spec

minFirefoxCapabilities :: FullCapabilities Source #

Returns the minimal FullCapabilities object for Firefox

minChromeCapabilities :: FullCapabilities Source #

Returns the minimal FullCapabilities object for Chrome

Errors

data WebDriverErrorType Source #

Known WevDriver error types: spec

Instances

Instances details
Bounded WebDriverErrorType Source # 
Instance details

Defined in WebDriverPreCore.Error

Enum WebDriverErrorType Source # 
Instance details

Defined in WebDriverPreCore.Error

Show WebDriverErrorType Source # 
Instance details

Defined in WebDriverPreCore.Error

Eq WebDriverErrorType Source # 
Instance details

Defined in WebDriverPreCore.Error

Ord WebDriverErrorType Source # 
Instance details

Defined in WebDriverPreCore.Error

Action Types

data Action Source #

Constructors

NoneAction 

Fields

Key 

Fields

Pointer 

Fields

Wheel 

Fields

Instances

Instances details
ToJSON Action Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Show Action Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Eq Action Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Methods

(==) :: Action -> Action -> Bool #

(/=) :: Action -> Action -> Bool #

data PointerAction Source #

newtype Actions Source #

Constructors

MkActions 

Fields

data Pointer Source #

Constructors

Mouse 
Pen 
Touch 

Instances

Instances details
ToJSON Pointer Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Show Pointer Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Eq Pointer Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Methods

(==) :: Pointer -> Pointer -> Bool #

(/=) :: Pointer -> Pointer -> Bool #

Auxiliary Spec Types

newtype WindowHandle Source #

Constructors

Handle 

Fields

data Selector Source #

Instances

Instances details
Show Selector Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Eq Selector Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

data Cookie Source #

Instances

Instances details
ToJSON Cookie Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Show Cookie Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Eq Cookie Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Methods

(==) :: Cookie -> Cookie -> Bool #

(/=) :: Cookie -> Cookie -> Bool #

newtype SessionId Source #

Constructors

Session 

Fields

Instances

Instances details
Show SessionId Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

newtype ElementId Source #

Constructors

Element 

Fields

Instances

Instances details
Generic ElementId Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Associated Types

type Rep ElementId 
Instance details

Defined in WebDriverPreCore.SpecDefinition

type Rep ElementId = D1 ('MetaData "ElementId" "WebDriverPreCore.SpecDefinition" "webdriver-precore-0.0.0.1-inplace" 'True) (C1 ('MetaCons "Element" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
Show ElementId Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Eq ElementId Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

type Rep ElementId Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

type Rep ElementId = D1 ('MetaData "ElementId" "WebDriverPreCore.SpecDefinition" "webdriver-precore-0.0.0.1-inplace" 'True) (C1 ('MetaCons "Element" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype UrlPath Source #

Url as returned by W3Spec The UrlPath type is a newtype wrapper around a list of Text segments representing a path.

e.g. the path: /session/session-no-1-2-3/window would be represented as: MkUrlPath ["session", "session-no-1-2-3", "window"]

Constructors

MkUrlPath 

Fields

Instances

Instances details
Semigroup UrlPath Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Show UrlPath Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Eq UrlPath Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

Methods

(==) :: UrlPath -> UrlPath -> Bool #

(/=) :: UrlPath -> UrlPath -> Bool #

Ord UrlPath Source # 
Instance details

Defined in WebDriverPreCore.SpecDefinition

data HttpResponse Source #

HttpResponse represents a WebDriver HTTP response.

Constructors

MkHttpResponse 

Fields

data Timeouts Source #

Timeouts in milliseconds spec

Constructors

MkTimeouts 

Instances

Instances details
FromJSON Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

ToJSON Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Generic Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Associated Types

type Rep Timeouts 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Timeouts = D1 ('MetaData "Timeouts" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkTimeouts" 'PrefixI 'True) (S1 ('MetaSel ('Just "implicit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "pageLoad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)))))

Methods

from :: Timeouts -> Rep Timeouts x #

to :: Rep Timeouts x -> Timeouts #

Show Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

Eq Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Timeouts Source # 
Instance details

Defined in WebDriverPreCore.Capabilities

type Rep Timeouts = D1 ('MetaData "Timeouts" "WebDriverPreCore.Capabilities" "webdriver-precore-0.0.0.1-inplace" 'False) (C1 ('MetaCons "MkTimeouts" 'PrefixI 'True) (S1 ('MetaSel ('Just "implicit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "pageLoad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)))))