{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-deriving-typeable #-}
module Test.WebDriver.Exceptions (
InvalidURL(..)
, NoSessionId(..)
, BadJSON(..)
, HTTPStatusUnknown(..)
, ServerError(..)
, FailedCommand(..)
, FailedCommandError(..)
, StackFrame(..)
) where
import Control.Exception (Exception)
import Data.Aeson
import Data.Aeson.TH
import Data.Text (Text)
import Data.Typeable (Typeable)
import GHC.Stack
import Prelude
import Test.WebDriver.Capabilities.Aeson
import Test.WebDriver.JSON
import Test.WebDriver.Types
newtype InvalidURL = InvalidURL String
deriving (InvalidURL -> InvalidURL -> Bool
(InvalidURL -> InvalidURL -> Bool)
-> (InvalidURL -> InvalidURL -> Bool) -> Eq InvalidURL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvalidURL -> InvalidURL -> Bool
== :: InvalidURL -> InvalidURL -> Bool
$c/= :: InvalidURL -> InvalidURL -> Bool
/= :: InvalidURL -> InvalidURL -> Bool
Eq, Int -> InvalidURL -> ShowS
[InvalidURL] -> ShowS
InvalidURL -> String
(Int -> InvalidURL -> ShowS)
-> (InvalidURL -> String)
-> ([InvalidURL] -> ShowS)
-> Show InvalidURL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvalidURL -> ShowS
showsPrec :: Int -> InvalidURL -> ShowS
$cshow :: InvalidURL -> String
show :: InvalidURL -> String
$cshowList :: [InvalidURL] -> ShowS
showList :: [InvalidURL] -> ShowS
Show, Typeable)
instance Exception InvalidURL
data HTTPStatusUnknown = HTTPStatusUnknown Int String
deriving (HTTPStatusUnknown -> HTTPStatusUnknown -> Bool
(HTTPStatusUnknown -> HTTPStatusUnknown -> Bool)
-> (HTTPStatusUnknown -> HTTPStatusUnknown -> Bool)
-> Eq HTTPStatusUnknown
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool
== :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool
$c/= :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool
/= :: HTTPStatusUnknown -> HTTPStatusUnknown -> Bool
Eq, Int -> HTTPStatusUnknown -> ShowS
[HTTPStatusUnknown] -> ShowS
HTTPStatusUnknown -> String
(Int -> HTTPStatusUnknown -> ShowS)
-> (HTTPStatusUnknown -> String)
-> ([HTTPStatusUnknown] -> ShowS)
-> Show HTTPStatusUnknown
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HTTPStatusUnknown -> ShowS
showsPrec :: Int -> HTTPStatusUnknown -> ShowS
$cshow :: HTTPStatusUnknown -> String
show :: HTTPStatusUnknown -> String
$cshowList :: [HTTPStatusUnknown] -> ShowS
showList :: [HTTPStatusUnknown] -> ShowS
Show, Typeable)
instance Exception HTTPStatusUnknown
newtype ServerError = ServerError String
deriving (ServerError -> ServerError -> Bool
(ServerError -> ServerError -> Bool)
-> (ServerError -> ServerError -> Bool) -> Eq ServerError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServerError -> ServerError -> Bool
== :: ServerError -> ServerError -> Bool
$c/= :: ServerError -> ServerError -> Bool
/= :: ServerError -> ServerError -> Bool
Eq, Int -> ServerError -> ShowS
[ServerError] -> ShowS
ServerError -> String
(Int -> ServerError -> ShowS)
-> (ServerError -> String)
-> ([ServerError] -> ShowS)
-> Show ServerError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServerError -> ShowS
showsPrec :: Int -> ServerError -> ShowS
$cshow :: ServerError -> String
show :: ServerError -> String
$cshowList :: [ServerError] -> ShowS
showList :: [ServerError] -> ShowS
Show, Typeable)
instance Exception ServerError
data FailedCommandError =
ElementClickIntercepted
| ElementNotInteractable
| InsecureCertificate
| InvalidArgument
| InvalidCookieDomain
| InvalidElementState
| InvalidSelector
| InvalidSessionId
| JavascriptError
| MoveTargetOutOfBounds
| NoSuchAlert
| NoSuchCookie
| NoSuchElement
| NoSuchFrame
| NoSuchWindow
| ScriptTimeout
| SessionNotCreated
| StaleElementReference
| Timeout
| UnableToSetCookie
| UnableToCaptureScreen
| UnexpectedAlertOpen
| UnknownCommand
| UnknownError
| UnknownMethod
| UnsupportedOperation
| UnparsedError Text
deriving (Int -> FailedCommandError -> ShowS
[FailedCommandError] -> ShowS
FailedCommandError -> String
(Int -> FailedCommandError -> ShowS)
-> (FailedCommandError -> String)
-> ([FailedCommandError] -> ShowS)
-> Show FailedCommandError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FailedCommandError -> ShowS
showsPrec :: Int -> FailedCommandError -> ShowS
$cshow :: FailedCommandError -> String
show :: FailedCommandError -> String
$cshowList :: [FailedCommandError] -> ShowS
showList :: [FailedCommandError] -> ShowS
Show, FailedCommandError -> FailedCommandError -> Bool
(FailedCommandError -> FailedCommandError -> Bool)
-> (FailedCommandError -> FailedCommandError -> Bool)
-> Eq FailedCommandError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FailedCommandError -> FailedCommandError -> Bool
== :: FailedCommandError -> FailedCommandError -> Bool
$c/= :: FailedCommandError -> FailedCommandError -> Bool
/= :: FailedCommandError -> FailedCommandError -> Bool
Eq)
deriveFromJSON toSpacedC0 ''FailedCommandError
deriveToJSON toSpacedC0 ''FailedCommandError
data FailedCommand = FailedCommand {
FailedCommand -> FailedCommandError
rspError :: FailedCommandError
, FailedCommand -> Text
rspMessage :: Text
, FailedCommand -> Text
rspStacktrace :: Text
, FailedCommand -> Maybe Value
rspData :: Maybe Value
} deriving (FailedCommand -> FailedCommand -> Bool
(FailedCommand -> FailedCommand -> Bool)
-> (FailedCommand -> FailedCommand -> Bool) -> Eq FailedCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FailedCommand -> FailedCommand -> Bool
== :: FailedCommand -> FailedCommand -> Bool
$c/= :: FailedCommand -> FailedCommand -> Bool
/= :: FailedCommand -> FailedCommand -> Bool
Eq, Int -> FailedCommand -> ShowS
[FailedCommand] -> ShowS
FailedCommand -> String
(Int -> FailedCommand -> ShowS)
-> (FailedCommand -> String)
-> ([FailedCommand] -> ShowS)
-> Show FailedCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FailedCommand -> ShowS
showsPrec :: Int -> FailedCommand -> ShowS
$cshow :: FailedCommand -> String
show :: FailedCommand -> String
$cshowList :: [FailedCommand] -> ShowS
showList :: [FailedCommand] -> ShowS
Show)
instance Exception FailedCommand
deriveFromJSON toCamel1 ''FailedCommand
data NoSessionId = NoSessionId String CallStack
deriving (Int -> NoSessionId -> ShowS
[NoSessionId] -> ShowS
NoSessionId -> String
(Int -> NoSessionId -> ShowS)
-> (NoSessionId -> String)
-> ([NoSessionId] -> ShowS)
-> Show NoSessionId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NoSessionId -> ShowS
showsPrec :: Int -> NoSessionId -> ShowS
$cshow :: NoSessionId -> String
show :: NoSessionId -> String
$cshowList :: [NoSessionId] -> ShowS
showList :: [NoSessionId] -> ShowS
Show, Typeable)
instance Exception NoSessionId