webdriver-0.9.0.1: a Haskell client for the Selenium WebDriver protocol

Safe HaskellNone
LanguageHaskell2010

Test.WebDriver.Types

Contents

Synopsis

WebDriver sessions

newtype WD a Source #

A state monad for WebDriver commands.

Constructors

WD (StateT WDSession IO a) 
Instances
Monad WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

(>>=) :: WD a -> (a -> WD b) -> WD b #

(>>) :: WD a -> WD b -> WD b #

return :: a -> WD a #

fail :: String -> WD a #

Functor WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

fmap :: (a -> b) -> WD a -> WD b #

(<$) :: a -> WD b -> WD a #

MonadFix WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

mfix :: (a -> WD a) -> WD a #

Applicative WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

pure :: a -> WD a #

(<*>) :: WD (a -> b) -> WD a -> WD b #

liftA2 :: (a -> b -> c) -> WD a -> WD b -> WD c #

(*>) :: WD a -> WD b -> WD b #

(<*) :: WD a -> WD b -> WD a #

MonadIO WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

liftIO :: IO a -> WD a #

MonadThrow WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

throwM :: Exception e => e -> WD a #

MonadCatch WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

catch :: Exception e => WD a -> (e -> WD a) -> WD a #

WDSessionState WD Source # 
Instance details

Defined in Test.WebDriver.Monad

WebDriver WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

doCommand :: (HasCallStack, ToJSON a, FromJSON b) => Method -> Text -> a -> WD b Source #

MonadBase IO WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Methods

liftBase :: IO α -> WD α #

MonadBaseControl IO WD Source # 
Instance details

Defined in Test.WebDriver.Monad

Associated Types

type StM WD a :: Type #

Methods

liftBaseWith :: (RunInBase WD IO -> IO a) -> WD a #

restoreM :: StM WD a -> WD a #

type StM WD a Source # 
Instance details

Defined in Test.WebDriver.Monad

type StM WD a = StM (StateT WDSession IO) a

data WDSession Source #

The local state of a WebDriver session. This structure is passed implicitly through all WD computations

Constructors

WDSession 

Fields

newtype SessionId Source #

An opaque identifier for a WebDriver session. These handles are produced by the server on session creation, and act to identify a session in progress.

Constructors

SessionId Text 

WebDriver configuration

data WDConfig Source #

WebDriver session configuration

Constructors

WDConfig 

Fields

defaultConfig :: WDConfig Source #

A default session config connects to localhost on port 4444, and hasn't been initialized server-side. This value is the same as def but with a less polymorphic type.

type SessionHistoryConfig = SessionHistory -> [SessionHistory] -> [SessionHistory] Source #

A function used by wdHistoryConfig to append new entries to session history.

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

defaultCaps :: Capabilities Source #

Default capabilities. This is the same as the Default instance, but with less polymorphism. By default, we use firefox of an unspecified version with default system-wide proxy settings on whatever platform is available . All Maybe capabilities are set to Nothing (no preference).

allCaps :: Capabilities Source #

Same as defaultCaps, but with all Maybe Value capabilities set to Just True.

data Platform Source #

Represents platform options supported by WebDriver. The value Any represents no preference.

Constructors

Windows 
XP 
Vista 
Mac 
Linux 
Unix 
Any 
Instances
Bounded Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Enum Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Eq Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Ord Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Show Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

ToJSON Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

FromJSON Platform Source # 
Instance details

Defined in Test.WebDriver.Capabilities

data ProxyType Source #

Available settings for the proxy Capabilities field

Constructors

NoProxy 
UseSystemSettings 
AutoDetect 
PAC

Use a proxy auto-config file specified by URL

Manual

Manually specify proxy hosts as hostname:port strings. Note that behavior is undefined for empty strings.

data UnexpectedAlertBehavior Source #

Instances
Bounded UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Enum UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Eq UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Ord UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Read UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Show UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

ToJSON UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

FromJSON UnexpectedAlertBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Browser-specific capabilities

data Browser Source #

This constructor simultaneously specifies which browser the session will use, while also providing browser-specific configuration. Default configuration is provided for each browser by firefox, chrome, opera, ie, etc.

This library uses firefox as its Default browser configuration, when no browser choice is specified.

Constructors

Firefox 

Fields

  • ffProfile :: Maybe (PreparedProfile Firefox)

    The firefox profile to use. If Nothing, a default temporary profile is automatically created and used.

  • ffLogPref :: LogLevel

    Firefox logging preference

  • ffBinary :: Maybe FilePath

    Server-side path to Firefox binary. If Nothing, use a sensible system-based default.

  • ffAcceptInsecureCerts :: Maybe Bool

    Available after Firefox 52, and required only for Firefox geckodriver. Indicates whether untrusted and self-signed TLS certificates are implicitly trusted on navigation for the duration of the session.

Chrome 

Fields

IE 

Fields

  • ieIgnoreProtectedModeSettings :: Bool

    Whether to skip the protected mode check. If set, tests may become flaky, unresponsive, or browsers may hang. If not set, and protected mode settings are not the same for all zones, an exception will be thrown on driver construction.

  • ieIgnoreZoomSetting :: Bool

    Indicates whether to skip the check that the browser's zoom level is set to 100%. Value is set to false by default.

  • ieInitialBrowserUrl :: Maybe Text

    Allows the user to specify the initial URL loaded when IE starts. Intended to be used with ignoreProtectedModeSettings to allow the user to initialize IE in the proper Protected Mode zone. Using this capability may cause browser instability or flaky and unresponsive code. Only "best effort" support is provided when using this capability.

  • ieElementScrollBehavior :: IEElementScrollBehavior

    Allows the user to specify whether elements are scrolled into the viewport for interaction to align with the top or bottom of the viewport. The default value is to align with the top of the viewport.

  • ieEnablePersistentHover :: Bool

    Determines whether persistent hovering is enabled (true by default). Persistent hovering is achieved by continuously firing mouse over events at the last location the mouse cursor has been moved to.

  • ieEnableElementCacheCleanup :: Bool

    Determines whether the driver should attempt to remove obsolete elements from the element cache on page navigation (true by default). This is to help manage the IE driver's memory footprint , removing references to invalid elements.

  • ieRequireWindowFocus :: Bool

    Determines whether to require that the IE window have focus before performing any user interaction operations (mouse or keyboard events). This capability is false by default, but delivers much more accurate native events interactions.

  • ieBrowserAttachTimeout :: Integer

    The timeout, in milliseconds, that the driver will attempt to locate and attach to a newly opened instance of Internet Explorer . The default is zero, which indicates waiting indefinitely.

  • ieLogFile :: Maybe FilePath

    The path to file where server should write log messages to. By default it writes to stdout.

  • ieLogLevel :: IELogLevel

    The log level used by the server. Defaults to IELogFatal

  • ieHost :: Maybe Text

    The address of the host adapter on which the server will listen for commands.

  • ieExtractPath :: Maybe Text

    The path to the directory used to extract supporting files used by the server. Defaults to the TEMP directory if not specified.

  • ieSilent :: Bool

    Suppresses diagnostic output when the server is started.

  • ieForceCreateProcess :: Bool

    Forces launching Internet Explorer using the CreateProcess API. If this option is not specified, IE is launched using the IELaunchURL, if it is available. For IE 8 and above, this option requires the TabProcGrowth registry value to be set to 0.

  • ieSwitches :: Maybe Text

    Specifies command-line switches with which to launch Internet Explorer. This is only valid when used with the forceCreateProcess.

Opera 

Fields

  • operaBinary :: Maybe FilePath

    Server-side path to the Opera binary

  • operaProduct :: Maybe String

    Which Opera product we're using, e.g. "desktop", "core"

  • operaDetach :: Bool

    Whether the Opera instance should stay open after we close the session. If false, closing the session closes the browser.

  • operaAutoStart :: Bool

    Whether to auto-start the Opera binary. If false, OperaDriver will wait for a connection from the browser. By default this is True.

  • operaIdle :: Bool

    Whether to use Opera's alternative implicit wait implementation. It will use an in-browser heuristic to guess when a page has finished loading. This feature is experimental, and disabled by default.

  • operaDisplay :: Maybe Int

    (*nix only) which X display to use.

  • operaLauncher :: Maybe FilePath

    Path to the launcher binary to use. The launcher is a gateway between OperaDriver and the Opera browser. If Nothing, OperaDriver will use the launcher supplied with the package.

  • operaPort :: Maybe Word16

    The port we should use to connect to Opera. If Just 0 , use a random port. If Nothing, use the default Opera port. The default opera constructor uses Just 0, since Nothing is likely to cause "address already in use" errors.

  • operaHost :: Maybe String

    The host Opera should connect to. Unless you're starting Opera manually you won't need this.

  • operaOptions :: Maybe String

    Command-line arguments to pass to Opera.

  • operaLogFile :: Maybe FilePath

    Where to send the log output. If Nothing, logging is disabled.

  • operaLogPref :: LogLevel

    Log level preference. Defaults to LogInfo

Phantomjs 
HTMLUnit 
IPhone 
IPad 
Android 
Browser Text

some other browser, specified by a string name

Default settings for browsers

firefox :: Browser Source #

Default Firefox settings. All Maybe fields are set to Nothing. ffLogPref is set to LogInfo.

chrome :: Browser Source #

Default Chrome settings. All Maybe fields are set to Nothing, no options are specified, and no extensions are used.

ie :: Browser Source #

Default IE settings. See the IE constructor for more details on individual defaults

opera :: Browser Source #

Default Opera settings. See the Opera constructor for more details on individual defaults.

data LogLevel Source #

Indicates a log verbosity level. Used in Browser and Opera configuration.

Instances
Bounded LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Enum LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Eq LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Ord LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Read LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Show LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

ToJSON LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

FromJSON LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Default LogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Methods

def :: LogLevel #

data IELogLevel Source #

Logging levels for Internet Explorer

Instances
Bounded IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Enum IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Eq IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Ord IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Read IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Show IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

ToJSON IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

FromJSON IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Default IELogLevel Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Methods

def :: IELogLevel #

data IEElementScrollBehavior Source #

Specifies how elements scroll into the viewport. (see ieElementScrollBehavior)

Constructors

AlignTop 
AlignBottom 
Instances
Bounded IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Enum IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Eq IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Ord IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Read IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Show IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

ToJSON IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

FromJSON IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

Default IEElementScrollBehavior Source # 
Instance details

Defined in Test.WebDriver.Capabilities

WebDriver objects and command-specific types

newtype WindowHandle Source #

An opaque identifier for a browser window

Constructors

WindowHandle Text 
Instances
Eq WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

Ord WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

Read WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

Show WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

ToJSON WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

FromJSON WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

Default WindowHandle Source # 
Instance details

Defined in Test.WebDriver.Commands.Internal

Methods

def :: WindowHandle #

currentWindow :: WindowHandle Source #

A special WindowHandle that always refers to the currently focused window. This is also used by the Default instance.

data Selector Source #

Specifies element(s) within a DOM tree using various selection methods.

Constructors

ById Text 
ByName Text 
ByClass Text

(Note: multiple classes are not allowed. For more control, use ByCSS)

ByTag Text 
ByLinkText Text 
ByPartialLinkText Text 
ByCSS Text 
ByXPath Text 

data JSArg Source #

An existential wrapper for any ToJSON instance. This allows us to pass parameters of many different types to Javascript code.

Constructors

ToJSON a => JSArg a 
Instances
ToJSON JSArg Source # 
Instance details

Defined in Test.WebDriver.Commands

data FrameSelector Source #

Specifies the frame used by focusFrame

Constructors

WithIndex Integer 
WithName Text

focus on a frame by name or ID

WithElement Element

focus on a frame Element

DefaultFrame

focus on the first frame, or the main document if iframes are used.

data Cookie Source #

Cookies are delicious delicacies. When sending cookies to the server, a value of Nothing indicates that the server should use a default value. When receiving cookies from the server, a value of Nothing indicates that the server is unable to specify the value.

Constructors

Cookie 

Fields

Instances
Eq Cookie Source # 
Instance details

Defined in Test.WebDriver.Commands

Methods

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

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

Show Cookie Source # 
Instance details

Defined in Test.WebDriver.Commands

ToJSON Cookie Source # 
Instance details

Defined in Test.WebDriver.Commands

FromJSON Cookie Source # 
Instance details

Defined in Test.WebDriver.Commands

mkCookie :: Text -> Text -> Cookie Source #

Creates a Cookie with only a name and value specified. All other fields are set to Nothing, which tells the server to use default values.

data Orientation Source #

A screen orientation

Constructors

Landscape 
Portrait 
Instances
Bounded Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

Enum Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

Eq Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

Ord Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

Show Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

ToJSON Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

FromJSON Orientation Source # 
Instance details

Defined in Test.WebDriver.Commands

data MouseButton Source #

A mouse button

Instances
Bounded MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

Enum MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

Eq MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

Ord MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

Show MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

ToJSON MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

FromJSON MouseButton Source # 
Instance details

Defined in Test.WebDriver.Commands

data WebStorageType Source #

An HTML 5 storage type

Instances
Bounded WebStorageType Source # 
Instance details

Defined in Test.WebDriver.Commands

Enum WebStorageType Source # 
Instance details

Defined in Test.WebDriver.Commands

Eq WebStorageType Source # 
Instance details

Defined in Test.WebDriver.Commands

Ord WebStorageType Source # 
Instance details

Defined in Test.WebDriver.Commands

Show WebStorageType Source # 
Instance details

Defined in Test.WebDriver.Commands

data LogEntry Source #

A record that represents a single log entry.

Constructors

LogEntry 

Fields

data ApplicationCacheStatus Source #

Instances
Bounded ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

Enum ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

Eq ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

Ord ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

Read ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

Show ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

FromJSON ApplicationCacheStatus Source # 
Instance details

Defined in Test.WebDriver.Commands

Exceptions

newtype NoSessionId Source #

A command requiring a session ID was attempted when no session ID was available.

Constructors

NoSessionId String 

newtype BadJSON Source #

An error occured when parsing a JSON value.

Constructors

BadJSON String 
Instances
Eq BadJSON Source # 
Instance details

Defined in Test.WebDriver.JSON

Methods

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

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

Show BadJSON Source # 
Instance details

Defined in Test.WebDriver.JSON

Exception BadJSON Source # 
Instance details

Defined in Test.WebDriver.JSON

data FailedCommand Source #

This exception encapsulates a broad variety of exceptions that can occur when a command fails.

data FailedCommandType Source #

The type of failed command exception that occured.

Instances
Bounded FailedCommandType Source # 
Instance details

Defined in Test.WebDriver.Exceptions.Internal

Enum FailedCommandType Source # 
Instance details

Defined in Test.WebDriver.Exceptions.Internal

Eq FailedCommandType Source # 
Instance details

Defined in Test.WebDriver.Exceptions.Internal

Ord FailedCommandType Source # 
Instance details

Defined in Test.WebDriver.Exceptions.Internal

Show FailedCommandType Source # 
Instance details

Defined in Test.WebDriver.Exceptions.Internal

data FailedCommandInfo Source #

Detailed information about the failed command provided by the server.

Constructors

FailedCommandInfo 

Fields

Instances
Show FailedCommandInfo Source #

Provides a readable printout of the error information, useful for logging.

Instance details

Defined in Test.WebDriver.Exceptions.Internal

FromJSON FailedCommandInfo Source # 
Instance details

Defined in Test.WebDriver.Exceptions.Internal

data StackFrame Source #

An individual stack frame from the stack trace provided by the server during a FailedCommand.

mkFailedCommandInfo :: WDSessionState s => String -> CallStack -> s FailedCommandInfo Source #

Constructs a FailedCommandInfo from only an error message.

failedCommand :: (HasCallStack, WDSessionStateIO s) => FailedCommandType -> String -> s a Source #

Convenience function to throw a FailedCommand locally with no server-side info present.