Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype InvalidURL = InvalidURL String
- data HTTPStatusUnknown = HTTPStatusUnknown Int String
- data HTTPConnError = HTTPConnError String Int
- newtype UnknownCommand = UnknownCommand String
- newtype ServerError = ServerError String
- data FailedCommand = FailedCommand FailedCommandType FailedCommandInfo
- failedCommand :: (HasCallStack, WDSessionStateIO s) => FailedCommandType -> String -> s a
- mkFailedCommandInfo :: WDSessionState s => String -> CallStack -> s 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 {}
- externalCallStack :: HasCallStack => CallStack
- callStackItemToStackFrame :: (String, SrcLoc) -> StackFrame
Documentation
newtype InvalidURL Source #
An invalid URL was given
Instances
Exception InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions.Internal toException :: InvalidURL -> SomeException # fromException :: SomeException -> Maybe InvalidURL # displayException :: InvalidURL -> String # | |
Show InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> InvalidURL -> ShowS # show :: InvalidURL -> String # showList :: [InvalidURL] -> ShowS # | |
Eq InvalidURL Source # | |
Defined in Test.WebDriver.Exceptions.Internal (==) :: InvalidURL -> InvalidURL -> Bool # (/=) :: InvalidURL -> InvalidURL -> Bool # |
data HTTPStatusUnknown Source #
An unexpected HTTP status was sent by the server.
Instances
Exception HTTPStatusUnknown Source # | |
Show HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> HTTPStatusUnknown -> ShowS # show :: HTTPStatusUnknown -> String # showList :: [HTTPStatusUnknown] -> ShowS # | |
Eq HTTPStatusUnknown Source # | |
Defined in Test.WebDriver.Exceptions.Internal (==) :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool # (/=) :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool # |
data HTTPConnError Source #
HTTP connection errors.
Instances
Exception HTTPConnError Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show HTTPConnError Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> HTTPConnError -> ShowS # show :: HTTPConnError -> String # showList :: [HTTPConnError] -> ShowS # | |
Eq HTTPConnError Source # | |
Defined in Test.WebDriver.Exceptions.Internal (==) :: HTTPConnError -> HTTPConnError -> Bool # (/=) :: HTTPConnError -> HTTPConnError -> Bool # |
newtype UnknownCommand Source #
A command was sent to the WebDriver server that it didn't recognize.
Instances
Exception UnknownCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show UnknownCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> UnknownCommand -> ShowS # show :: UnknownCommand -> String # showList :: [UnknownCommand] -> ShowS # | |
Eq UnknownCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal (==) :: UnknownCommand -> UnknownCommand -> Bool # (/=) :: UnknownCommand -> UnknownCommand -> Bool # |
newtype ServerError Source #
A server-side exception occured
Instances
Exception ServerError Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show ServerError Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> ServerError -> ShowS # show :: ServerError -> String # showList :: [ServerError] -> ShowS # | |
Eq ServerError Source # | |
Defined in Test.WebDriver.Exceptions.Internal (==) :: ServerError -> ServerError -> Bool # (/=) :: ServerError -> ServerError -> Bool # |
data FailedCommand Source #
This exception encapsulates a broad variety of exceptions that can occur when a command fails.
Instances
Exception FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal | |
Show FailedCommand Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> FailedCommand -> ShowS # show :: FailedCommand -> String # showList :: [FailedCommand] -> ShowS # |
failedCommand :: (HasCallStack, WDSessionStateIO s) => FailedCommandType -> String -> s a Source #
Convenience function to throw a FailedCommand
locally with no server-side
info present.
mkFailedCommandInfo :: WDSessionState s => String -> CallStack -> s FailedCommandInfo Source #
Constructs a FailedCommandInfo from only an error message.
data FailedCommandType Source #
The type of failed command exception that occured.
Instances
data FailedCommandInfo Source #
Detailed information about the failed command provided by the server.
FailedCommandInfo | |
|
Instances
FromJSON FailedCommandInfo Source # | |
Defined in Test.WebDriver.Exceptions.Internal parseJSON :: Value -> Parser FailedCommandInfo # parseJSONList :: Value -> Parser [FailedCommandInfo] # | |
Show FailedCommandInfo Source # | Provides a readable printout of the error information, useful for logging. |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> FailedCommandInfo -> ShowS # show :: FailedCommandInfo -> String # showList :: [FailedCommandInfo] -> ShowS # |
data StackFrame Source #
An individual stack frame from the stack trace provided by the server during a FailedCommand.
StackFrame | |
|
Instances
FromJSON StackFrame Source # | |
Defined in Test.WebDriver.Exceptions.Internal parseJSON :: Value -> Parser StackFrame # parseJSONList :: Value -> Parser [StackFrame] # | |
Show StackFrame Source # | |
Defined in Test.WebDriver.Exceptions.Internal showsPrec :: Int -> StackFrame -> ShowS # show :: StackFrame -> String # showList :: [StackFrame] -> ShowS # | |
Eq StackFrame Source # | |
Defined in Test.WebDriver.Exceptions.Internal (==) :: StackFrame -> StackFrame -> Bool # (/=) :: StackFrame -> StackFrame -> Bool # |
externalCallStack :: HasCallStack => CallStack Source #
Use GHC's CallStack capabilities to return a callstack to help debug a FailedCommand. Drops all stack frames inside Test.WebDriver modules, so the first frame on the stack should be where the user called into Test.WebDriver
callStackItemToStackFrame :: (String, SrcLoc) -> StackFrame Source #