Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.WebDriver.Types
Contents
Synopsis
- newtype WD a = WD (StateT WDSession IO a)
- data WDSession = WDSession {}
- newtype SessionId = SessionId Text
- data SessionHistory
- data WDConfig = WDConfig {}
- defaultConfig :: WDConfig
- type SessionHistoryConfig = SessionHistory -> [SessionHistory] -> [SessionHistory]
- data Capabilities = Capabilities {
- browser :: Browser
- version :: Maybe String
- platform :: Platform
- proxy :: ProxyType
- javascriptEnabled :: Maybe Bool
- takesScreenshot :: Maybe Bool
- handlesAlerts :: Maybe Bool
- databaseEnabled :: Maybe Bool
- locationContextEnabled :: Maybe Bool
- applicationCacheEnabled :: Maybe Bool
- browserConnectionEnabled :: Maybe Bool
- cssSelectorsEnabled :: Maybe Bool
- webStorageEnabled :: Maybe Bool
- rotatable :: Maybe Bool
- acceptSSLCerts :: Maybe Bool
- nativeEvents :: Maybe Bool
- unexpectedAlertBehavior :: Maybe UnexpectedAlertBehavior
- additionalCaps :: [Pair]
- defaultCaps :: Capabilities
- allCaps :: Capabilities
- data Platform
- data ProxyType
- = NoProxy
- | UseSystemSettings
- | AutoDetect
- | PAC { }
- | Manual { }
- data UnexpectedAlertBehavior
- data Browser
- = Firefox { }
- | Chrome { }
- | IE {
- ieIgnoreProtectedModeSettings :: Bool
- ieIgnoreZoomSetting :: Bool
- ieInitialBrowserUrl :: Maybe Text
- ieElementScrollBehavior :: IEElementScrollBehavior
- ieEnablePersistentHover :: Bool
- ieEnableElementCacheCleanup :: Bool
- ieRequireWindowFocus :: Bool
- ieBrowserAttachTimeout :: Integer
- ieLogFile :: Maybe FilePath
- ieLogLevel :: IELogLevel
- ieHost :: Maybe Text
- ieExtractPath :: Maybe Text
- ieSilent :: Bool
- ieForceCreateProcess :: Bool
- ieSwitches :: Maybe Text
- | Opera {
- operaBinary :: Maybe FilePath
- operaProduct :: Maybe String
- operaDetach :: Bool
- operaAutoStart :: Bool
- operaIdle :: Bool
- operaDisplay :: Maybe Int
- operaLauncher :: Maybe FilePath
- operaPort :: Maybe Word16
- operaHost :: Maybe String
- operaOptions :: Maybe String
- operaLogFile :: Maybe FilePath
- operaLogPref :: LogLevel
- | Phantomjs { }
- | HTMLUnit
- | IPhone
- | IPad
- | Android
- | Browser Text
- firefox :: Browser
- chrome :: Browser
- ie :: Browser
- opera :: Browser
- iPhone :: Browser
- iPad :: Browser
- android :: Browser
- data LogLevel
- data IELogLevel
- data IEElementScrollBehavior
- newtype Element = Element Text
- newtype WindowHandle = WindowHandle Text
- currentWindow :: WindowHandle
- data Selector
- data JSArg = ToJSON a => JSArg a
- data FrameSelector
- data Cookie = Cookie {}
- mkCookie :: Text -> Text -> Cookie
- data Orientation
- data MouseButton
- data WebStorageType
- type LogType = String
- data LogEntry = LogEntry {}
- data ApplicationCacheStatus
- newtype InvalidURL = InvalidURL String
- newtype NoSessionId = NoSessionId String
- newtype BadJSON = BadJSON String
- data HTTPStatusUnknown = HTTPStatusUnknown Int String
- data HTTPConnError = HTTPConnError String Int
- newtype UnknownCommand = UnknownCommand String
- newtype ServerError = ServerError String
- data FailedCommand = FailedCommand FailedCommandType FailedCommandInfo
- data FailedCommandType
- = NoSuchElement
- | NoSuchFrame
- | UnknownFrame
- | StaleElementReference
- | ElementNotVisible
- | InvalidElementState
- | UnknownError
- | ElementIsNotSelectable
- | JavascriptError
- | XPathLookupError
- | Timeout
- | NoSuchWindow
- | InvalidCookieDomain
- | UnableToSetCookie
- | UnexpectedAlertOpen
- | NoAlertOpen
- | ScriptTimeout
- | InvalidElementCoordinates
- | IMENotAvailable
- | IMEEngineActivationFailed
- | InvalidSelector
- | SessionNotCreated
- | MoveTargetOutOfBounds
- | InvalidXPathSelector
- | InvalidXPathSelectorReturnType
- data FailedCommandInfo = FailedCommandInfo {}
- data StackFrame = StackFrame {}
- mkFailedCommandInfo :: WDSessionState s => String -> CallStack -> s FailedCommandInfo
- failedCommand :: (HasCallStack, WDSessionStateIO s) => FailedCommandType -> String -> s a
WebDriver sessions
A state monad for WebDriver commands.
Instances
Monad WD Source # | |
Functor WD Source # | |
MonadFix WD Source # | |
Defined in Test.WebDriver.Monad | |
Applicative WD Source # | |
MonadIO WD Source # | |
Defined in Test.WebDriver.Monad | |
MonadThrow WD Source # | |
Defined in Test.WebDriver.Monad | |
MonadCatch WD Source # | |
WDSessionState WD Source # | |
Defined in Test.WebDriver.Monad | |
WebDriver WD Source # | |
Defined in Test.WebDriver.Monad | |
MonadBase IO WD Source # | |
Defined in Test.WebDriver.Monad | |
MonadBaseControl IO WD Source # | |
type StM WD a Source # | |
The local state of a WebDriver session. This structure is passed
implicitly through all WD
computations
Constructors
WDSession | |
Fields
|
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.
Instances
Eq SessionId Source # | |
Ord SessionId Source # | |
Read SessionId Source # | |
Show SessionId Source # | |
ToJSON SessionId Source # | |
Defined in Test.WebDriver.Session | |
FromJSON SessionId Source # | |
data SessionHistory Source #
Instances
Show SessionHistory Source # | |
Defined in Test.WebDriver.Session.History Methods showsPrec :: Int -> SessionHistory -> ShowS # show :: SessionHistory -> String # showList :: [SessionHistory] -> ShowS # |
WebDriver configuration
WebDriver session configuration
Constructors
WDConfig | |
Fields
|
Instances
Default WDConfig Source # | |
Defined in Test.WebDriver.Config | |
SetCapabilities WDConfig Source # | |
Defined in Test.WebDriver.Config | |
GetCapabilities WDConfig Source # | |
Defined in Test.WebDriver.Config Methods getCaps :: WDConfig -> Capabilities Source # | |
WebDriverConfig WDConfig Source # | |
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
|
Instances
Eq Capabilities Source # | |
Defined in Test.WebDriver.Capabilities | |
Show Capabilities Source # | |
Defined in Test.WebDriver.Capabilities Methods showsPrec :: Int -> Capabilities -> ShowS # show :: Capabilities -> String # showList :: [Capabilities] -> ShowS # | |
ToJSON Capabilities Source # | |
Defined in Test.WebDriver.Capabilities Methods toJSON :: Capabilities -> Value # toEncoding :: Capabilities -> Encoding # toJSONList :: [Capabilities] -> Value # toEncodingList :: [Capabilities] -> Encoding # | |
FromJSON Capabilities Source # | |
Defined in Test.WebDriver.Capabilities | |
Default Capabilities Source # | |
Defined in Test.WebDriver.Capabilities Methods def :: Capabilities # | |
GetCapabilities Capabilities Source # | |
Defined in Test.WebDriver.Capabilities Methods getCaps :: Capabilities -> Capabilities Source # |
allCaps :: Capabilities Source #
Same as defaultCaps
, but with all Maybe
Value
capabilities set to
Just
True
.
Represents platform options supported by WebDriver. The value Any represents no preference.
Instances
Bounded Platform Source # | |
Enum Platform Source # | |
Defined in Test.WebDriver.Capabilities | |
Eq Platform Source # | |
Ord Platform Source # | |
Defined in Test.WebDriver.Capabilities | |
Show Platform Source # | |
ToJSON Platform Source # | |
Defined in Test.WebDriver.Capabilities | |
FromJSON Platform Source # | |
Available settings for the proxy Capabilities
field
Constructors
NoProxy | |
UseSystemSettings | |
AutoDetect | |
PAC | Use a proxy auto-config file specified by URL |
Fields | |
Manual | Manually specify proxy hosts as hostname:port strings. Note that behavior is undefined for empty strings. |
data UnexpectedAlertBehavior Source #
Constructors
AcceptAlert | |
DismissAlert | |
IgnoreAlert |
Instances
Browser-specific capabilities
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
| |
Chrome | |
Fields
| |
IE | |
Fields
| |
Opera | |
Fields
| |
Phantomjs | |
Fields | |
HTMLUnit | |
IPhone | |
IPad | |
Android | |
Browser Text | some other browser, specified by a string name |
Default settings for browsers
Default Firefox settings. All Maybe fields are set to Nothing. ffLogPref
is set to LogInfo
.
Default Chrome settings. All Maybe fields are set to Nothing, no options are specified, and no extensions are used.
Default IE settings. See the IE
constructor for more details on
individual defaults
Default Opera settings. See the Opera
constructor for more details on
individual defaults.
Constructors
LogOff | |
LogSevere | |
LogWarning | |
LogInfo | |
LogConfig | |
LogFine | |
LogFiner | |
LogFinest | |
LogDebug | |
LogAll |
Instances
Bounded LogLevel Source # | |
Enum LogLevel Source # | |
Defined in Test.WebDriver.Capabilities | |
Eq LogLevel Source # | |
Ord LogLevel Source # | |
Defined in Test.WebDriver.Capabilities | |
Read LogLevel Source # | |
Show LogLevel Source # | |
ToJSON LogLevel Source # | |
Defined in Test.WebDriver.Capabilities | |
FromJSON LogLevel Source # | |
Default LogLevel Source # | |
Defined in Test.WebDriver.Capabilities |
data IELogLevel Source #
Logging levels for Internet Explorer
Constructors
IELogTrace | |
IELogDebug | |
IELogInfo | |
IELogWarn | |
IELogError | |
IELogFatal |
Instances
data IEElementScrollBehavior Source #
Specifies how elements scroll into the viewport. (see ieElementScrollBehavior
)
Constructors
AlignTop | |
AlignBottom |
Instances
WebDriver objects and command-specific types
An opaque identifier for a web page element.
newtype WindowHandle Source #
An opaque identifier for a browser window
Constructors
WindowHandle Text |
Instances
currentWindow :: WindowHandle Source #
A special WindowHandle
that always refers to the currently focused window.
This is also used by the Default
instance.
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 |
ByTag Text | |
ByLinkText Text | |
ByPartialLinkText Text | |
ByCSS Text | |
ByXPath Text |
An existential wrapper for any ToJSON
instance. This allows us to pass
parameters of many different types to Javascript code.
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 |
DefaultFrame | focus on the first frame, or the main document if iframes are used. |
Instances
Eq FrameSelector Source # | |
Defined in Test.WebDriver.Commands Methods (==) :: FrameSelector -> FrameSelector -> Bool # (/=) :: FrameSelector -> FrameSelector -> Bool # | |
Read FrameSelector Source # | |
Defined in Test.WebDriver.Commands Methods readsPrec :: Int -> ReadS FrameSelector # readList :: ReadS [FrameSelector] # | |
Show FrameSelector Source # | |
Defined in Test.WebDriver.Commands Methods showsPrec :: Int -> FrameSelector -> ShowS # show :: FrameSelector -> String # showList :: [FrameSelector] -> ShowS # | |
ToJSON FrameSelector Source # | |
Defined in Test.WebDriver.Commands Methods toJSON :: FrameSelector -> Value # toEncoding :: FrameSelector -> Encoding # toJSONList :: [FrameSelector] -> Value # toEncodingList :: [FrameSelector] -> Encoding # |
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
|
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
Instances
data MouseButton Source #
A mouse button
Constructors
LeftButton | |
MiddleButton | |
RightButton |
Instances
data WebStorageType Source #
An HTML 5 storage type
Constructors
LocalStorage | |
SessionStorage |
Instances
A record that represents a single log entry.
Constructors
LogEntry | |
data ApplicationCacheStatus Source #
Constructors
Uncached | |
Idle | |
Checking | |
Downloading | |
UpdateReady | |
Obsolete |
Instances
Exceptions
newtype InvalidURL Source #
An invalid URL was given
Constructors
InvalidURL String |
Instances
Eq InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> InvalidURL -> ShowS # show :: InvalidURL -> String # showList :: [InvalidURL] -> ShowS # | |
Exception InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods toException :: InvalidURL -> SomeException # fromException :: SomeException -> Maybe InvalidURL # displayException :: InvalidURL -> String # |
newtype NoSessionId Source #
A command requiring a session ID was attempted when no session ID was available.
Constructors
NoSessionId String |
Instances
Eq NoSessionId Source # | |
Defined in Test.WebDriver.Commands.Internal | |
Show NoSessionId Source # | |
Defined in Test.WebDriver.Commands.Internal Methods showsPrec :: Int -> NoSessionId -> ShowS # show :: NoSessionId -> String # showList :: [NoSessionId] -> ShowS # | |
Exception NoSessionId Source # | |
Defined in Test.WebDriver.Commands.Internal Methods toException :: NoSessionId -> SomeException # fromException :: SomeException -> Maybe NoSessionId # displayException :: NoSessionId -> String # |
An error occured when parsing a JSON value.
Instances
Eq BadJSON Source # | |
Show BadJSON Source # | |
Exception BadJSON Source # | |
Defined in Test.WebDriver.JSON Methods toException :: BadJSON -> SomeException # fromException :: SomeException -> Maybe BadJSON # displayException :: BadJSON -> String # |
data HTTPStatusUnknown Source #
An unexpected HTTP status was sent by the server.
Constructors
HTTPStatusUnknown Int String |
Instances
Eq HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods (==) :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool # (/=) :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool # | |
Show HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> HTTPStatusUnknown -> ShowS # show :: HTTPStatusUnknown -> String # showList :: [HTTPStatusUnknown] -> ShowS # | |
Exception HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods toException :: HTTPStatusUnknown -> SomeException # |
data HTTPConnError Source #
HTTP connection errors.
Constructors
HTTPConnError String Int |
Instances
Eq HTTPConnError Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods (==) :: HTTPConnError -> HTTPConnError -> Bool # (/=) :: HTTPConnError -> HTTPConnError -> Bool # | |
Show HTTPConnError Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> HTTPConnError -> ShowS # show :: HTTPConnError -> String # showList :: [HTTPConnError] -> ShowS # | |
Exception HTTPConnError Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods toException :: HTTPConnError -> SomeException # fromException :: SomeException -> Maybe HTTPConnError # displayException :: HTTPConnError -> String # |
newtype UnknownCommand Source #
A command was sent to the WebDriver server that it didn't recognize.
Constructors
UnknownCommand String |
Instances
Eq UnknownCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods (==) :: UnknownCommand -> UnknownCommand -> Bool # (/=) :: UnknownCommand -> UnknownCommand -> Bool # | |
Show UnknownCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> UnknownCommand -> ShowS # show :: UnknownCommand -> String # showList :: [UnknownCommand] -> ShowS # | |
Exception UnknownCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods toException :: UnknownCommand -> SomeException # |
newtype ServerError Source #
A server-side exception occured
Constructors
ServerError String |
Instances
Eq ServerError Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show ServerError Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> ServerError -> ShowS # show :: ServerError -> String # showList :: [ServerError] -> ShowS # | |
Exception ServerError Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods toException :: ServerError -> SomeException # fromException :: SomeException -> Maybe ServerError # displayException :: ServerError -> String # |
data FailedCommand Source #
This exception encapsulates a broad variety of exceptions that can occur when a command fails.
Constructors
FailedCommand FailedCommandType FailedCommandInfo |
Instances
Show FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> FailedCommand -> ShowS # show :: FailedCommand -> String # showList :: [FailedCommand] -> ShowS # | |
Exception FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods toException :: FailedCommand -> SomeException # fromException :: SomeException -> Maybe FailedCommand # displayException :: FailedCommand -> String # |
data FailedCommandType Source #
The type of failed command exception that occured.
Constructors
Instances
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. |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> FailedCommandInfo -> ShowS # show :: FailedCommandInfo -> String # showList :: [FailedCommandInfo] -> ShowS # | |
FromJSON FailedCommandInfo Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods parseJSON :: Value -> Parser FailedCommandInfo # parseJSONList :: Value -> Parser [FailedCommandInfo] # |
data StackFrame Source #
An individual stack frame from the stack trace provided by the server during a FailedCommand.
Constructors
StackFrame | |
Fields
|
Instances
Eq StackFrame Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show StackFrame Source # | |
Defined in Test.WebDriver.Exceptions.Internal Methods showsPrec :: Int -> StackFrame -> ShowS # show :: StackFrame -> String # showList :: [StackFrame] -> ShowS # | |
FromJSON StackFrame Source # | |
Defined in Test.WebDriver.Exceptions.Internal |
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.