{-# OPTIONS_HADDOCK hide #-}
module WebDriverPreCore.Error (
WebDriverErrorType(..),
ErrorClassification(..),
errorDescription,
errorCodeToErrorType,
errorTypeToErrorCode,
parseWebDriverError,
parseWebDriverErrorType
) where
import Data.Aeson (Value, withObject)
import Data.Aeson.Types ((.:), parseMaybe)
import Data.Text (Text)
import Data.Eq (Eq)
import GHC.Show (Show)
import Data.Ord (Ord)
import Data.Maybe (Maybe (..))
import WebDriverPreCore.HttpResponse (HttpResponse (..))
import GHC.Enum ( Bounded, Enum )
import Data.Either (Either (..))
import Control.Monad ((>>=))
import Data.Function (($))
data WebDriverErrorType =
ElementClickIntercepted |
ElementNotInteractable |
InsecureCertificate |
InvalidArgument |
InvalidCookieDomain |
InvalidElementState |
InvalidSelector |
InvalidSessionId |
JavascriptError |
MoveTargetOutOfBounds |
NoSuchAlert |
NoSuchCookie |
NoSuchElement |
NoSuchFrame |
NoSuchWindow |
NoSuchShadowRoot |
ScriptTimeoutError |
SessionNotCreated |
StaleElementReference |
DetachedShadowRoot |
Timeout |
UnableToSetCookie |
UnableToCaptureScreen |
UnexpectedAlertOpen |
UnknownCommand |
UnknownError |
UnknownMethod |
UnsupportedOperation
deriving (WebDriverErrorType -> WebDriverErrorType -> Bool
(WebDriverErrorType -> WebDriverErrorType -> Bool)
-> (WebDriverErrorType -> WebDriverErrorType -> Bool)
-> Eq WebDriverErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebDriverErrorType -> WebDriverErrorType -> Bool
== :: WebDriverErrorType -> WebDriverErrorType -> Bool
$c/= :: WebDriverErrorType -> WebDriverErrorType -> Bool
/= :: WebDriverErrorType -> WebDriverErrorType -> Bool
Eq, Int -> WebDriverErrorType -> ShowS
[WebDriverErrorType] -> ShowS
WebDriverErrorType -> String
(Int -> WebDriverErrorType -> ShowS)
-> (WebDriverErrorType -> String)
-> ([WebDriverErrorType] -> ShowS)
-> Show WebDriverErrorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WebDriverErrorType -> ShowS
showsPrec :: Int -> WebDriverErrorType -> ShowS
$cshow :: WebDriverErrorType -> String
show :: WebDriverErrorType -> String
$cshowList :: [WebDriverErrorType] -> ShowS
showList :: [WebDriverErrorType] -> ShowS
Show, Eq WebDriverErrorType
Eq WebDriverErrorType =>
(WebDriverErrorType -> WebDriverErrorType -> Ordering)
-> (WebDriverErrorType -> WebDriverErrorType -> Bool)
-> (WebDriverErrorType -> WebDriverErrorType -> Bool)
-> (WebDriverErrorType -> WebDriverErrorType -> Bool)
-> (WebDriverErrorType -> WebDriverErrorType -> Bool)
-> (WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType)
-> (WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType)
-> Ord WebDriverErrorType
WebDriverErrorType -> WebDriverErrorType -> Bool
WebDriverErrorType -> WebDriverErrorType -> Ordering
WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WebDriverErrorType -> WebDriverErrorType -> Ordering
compare :: WebDriverErrorType -> WebDriverErrorType -> Ordering
$c< :: WebDriverErrorType -> WebDriverErrorType -> Bool
< :: WebDriverErrorType -> WebDriverErrorType -> Bool
$c<= :: WebDriverErrorType -> WebDriverErrorType -> Bool
<= :: WebDriverErrorType -> WebDriverErrorType -> Bool
$c> :: WebDriverErrorType -> WebDriverErrorType -> Bool
> :: WebDriverErrorType -> WebDriverErrorType -> Bool
$c>= :: WebDriverErrorType -> WebDriverErrorType -> Bool
>= :: WebDriverErrorType -> WebDriverErrorType -> Bool
$cmax :: WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType
max :: WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType
$cmin :: WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType
min :: WebDriverErrorType -> WebDriverErrorType -> WebDriverErrorType
Ord, WebDriverErrorType
WebDriverErrorType
-> WebDriverErrorType -> Bounded WebDriverErrorType
forall a. a -> a -> Bounded a
$cminBound :: WebDriverErrorType
minBound :: WebDriverErrorType
$cmaxBound :: WebDriverErrorType
maxBound :: WebDriverErrorType
Bounded, Int -> WebDriverErrorType
WebDriverErrorType -> Int
WebDriverErrorType -> [WebDriverErrorType]
WebDriverErrorType -> WebDriverErrorType
WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
WebDriverErrorType
-> WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
(WebDriverErrorType -> WebDriverErrorType)
-> (WebDriverErrorType -> WebDriverErrorType)
-> (Int -> WebDriverErrorType)
-> (WebDriverErrorType -> Int)
-> (WebDriverErrorType -> [WebDriverErrorType])
-> (WebDriverErrorType
-> WebDriverErrorType -> [WebDriverErrorType])
-> (WebDriverErrorType
-> WebDriverErrorType -> [WebDriverErrorType])
-> (WebDriverErrorType
-> WebDriverErrorType
-> WebDriverErrorType
-> [WebDriverErrorType])
-> Enum WebDriverErrorType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: WebDriverErrorType -> WebDriverErrorType
succ :: WebDriverErrorType -> WebDriverErrorType
$cpred :: WebDriverErrorType -> WebDriverErrorType
pred :: WebDriverErrorType -> WebDriverErrorType
$ctoEnum :: Int -> WebDriverErrorType
toEnum :: Int -> WebDriverErrorType
$cfromEnum :: WebDriverErrorType -> Int
fromEnum :: WebDriverErrorType -> Int
$cenumFrom :: WebDriverErrorType -> [WebDriverErrorType]
enumFrom :: WebDriverErrorType -> [WebDriverErrorType]
$cenumFromThen :: WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
enumFromThen :: WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
$cenumFromTo :: WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
enumFromTo :: WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
$cenumFromThenTo :: WebDriverErrorType
-> WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
enumFromThenTo :: WebDriverErrorType
-> WebDriverErrorType -> WebDriverErrorType -> [WebDriverErrorType]
Enum)
getError :: Value -> Maybe Text
getError :: Value -> Maybe Text
getError =
(Value -> Parser Text) -> Value -> Maybe Text
forall a b. (a -> Parser b) -> a -> Maybe b
parseMaybe ((Value -> Parser Text) -> Value -> Maybe Text)
-> (Value -> Parser Text) -> Value -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> (Object -> Parser Text) -> Value -> Parser Text
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"root" ((Object -> Parser Text) -> Value -> Parser Text)
-> (Object -> Parser Text) -> Value -> Parser Text
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"value" Parser Value -> (Value -> Parser Text) -> Parser Text
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> (Object -> Parser Text) -> Value -> Parser Text
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"inner" (Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"error")
errorCodeToErrorType :: Text -> Either Text WebDriverErrorType
errorCodeToErrorType :: Text -> Either Text WebDriverErrorType
errorCodeToErrorType Text
errCode =
case Text
errCode of
Text
"element click intercepted" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
ElementClickIntercepted
Text
"element not interactable" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
ElementNotInteractable
Text
"insecure certificate" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
InsecureCertificate
Text
"invalid argument" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
InvalidArgument
Text
"invalid cookie domain" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
InvalidCookieDomain
Text
"invalid element state" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
InvalidElementState
Text
"invalid selector" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
InvalidSelector
Text
"invalid session id" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
InvalidSessionId
Text
"javascript error" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
JavascriptError
Text
"move target out of bounds" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
MoveTargetOutOfBounds
Text
"no such alert" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
NoSuchAlert
Text
"no such cookie" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
NoSuchCookie
Text
"no such element" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
NoSuchElement
Text
"no such frame" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
NoSuchFrame
Text
"no such window" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
NoSuchWindow
Text
"no such shadow root" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
NoSuchShadowRoot
Text
"script timeout" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
ScriptTimeoutError
Text
"session not created" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
SessionNotCreated
Text
"stale element reference" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
StaleElementReference
Text
"detached shadow root" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
DetachedShadowRoot
Text
"timeout" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
Timeout
Text
"unable to set cookie" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnableToSetCookie
Text
"unable to capture screen" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnableToCaptureScreen
Text
"unexpected alert open" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnexpectedAlertOpen
Text
"unknown command" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnknownCommand
Text
"unknown error" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnknownError
Text
"unknown method" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnknownMethod
Text
"unsupported operation" -> WebDriverErrorType -> Either Text WebDriverErrorType
forall {b} {a}. b -> Either a b
r WebDriverErrorType
UnsupportedOperation
Text
er -> Text -> Either Text WebDriverErrorType
forall a b. a -> Either a b
Left Text
er
where
r :: b -> Either a b
r = b -> Either a b
forall a b. b -> Either a b
Right
errorTypeToErrorCode :: WebDriverErrorType -> Text
errorTypeToErrorCode :: WebDriverErrorType -> Text
errorTypeToErrorCode = \case
WebDriverErrorType
ElementClickIntercepted -> Text
"element click intercepted"
WebDriverErrorType
ElementNotInteractable -> Text
"element not interactable"
WebDriverErrorType
InsecureCertificate -> Text
"insecure certificate"
WebDriverErrorType
InvalidArgument -> Text
"invalid argument"
WebDriverErrorType
InvalidCookieDomain -> Text
"invalid cookie domain"
WebDriverErrorType
InvalidElementState -> Text
"invalid element state"
WebDriverErrorType
InvalidSelector -> Text
"invalid selector"
WebDriverErrorType
InvalidSessionId -> Text
"invalid session id"
WebDriverErrorType
JavascriptError -> Text
"javascript error"
WebDriverErrorType
MoveTargetOutOfBounds -> Text
"move target out of bounds"
WebDriverErrorType
NoSuchAlert -> Text
"no such alert"
WebDriverErrorType
NoSuchCookie -> Text
"no such cookie"
WebDriverErrorType
NoSuchElement -> Text
"no such element"
WebDriverErrorType
NoSuchFrame -> Text
"no such frame"
WebDriverErrorType
NoSuchWindow -> Text
"no such window"
WebDriverErrorType
NoSuchShadowRoot -> Text
"no such shadow root"
WebDriverErrorType
ScriptTimeoutError -> Text
"script timeout"
WebDriverErrorType
SessionNotCreated -> Text
"session not created"
WebDriverErrorType
StaleElementReference -> Text
"stale element reference"
WebDriverErrorType
DetachedShadowRoot -> Text
"detached shadow root"
WebDriverErrorType
Timeout -> Text
"timeout"
WebDriverErrorType
UnableToSetCookie -> Text
"unable to set cookie"
WebDriverErrorType
UnableToCaptureScreen -> Text
"unable to capture screen"
WebDriverErrorType
UnexpectedAlertOpen -> Text
"unexpected alert open"
WebDriverErrorType
UnknownCommand -> Text
"unknown command"
WebDriverErrorType
UnknownError -> Text
"unknown error"
WebDriverErrorType
UnknownMethod -> Text
"unknown method"
WebDriverErrorType
UnsupportedOperation -> Text
"unsupported operation"
errorDescription :: WebDriverErrorType -> Text
errorDescription :: WebDriverErrorType -> Text
errorDescription = \case
WebDriverErrorType
ElementClickIntercepted -> Text
"The Element Click command could not be completed because the element receiving the events is obscuring the element that was requested clicked"
WebDriverErrorType
ElementNotInteractable -> Text
"A command could not be completed because the element is not pointer- or keyboard interactable"
WebDriverErrorType
InsecureCertificate -> Text
"Navigation caused the user agent to hit a certificate warning, which is usually the result of an expired or invalid TLS certificate"
WebDriverErrorType
InvalidArgument -> Text
"The arguments passed to a command are either invalid or malformed"
WebDriverErrorType
InvalidCookieDomain -> Text
"An illegal attempt was made to set a cookie under a different domain than the current page"
WebDriverErrorType
InvalidElementState -> Text
"A command could not be completed because the element is in an invalid state, e.g. attempting to clear an element that isn't both editable and resettable"
WebDriverErrorType
InvalidSelector -> Text
"Argument was an invalid selector"
WebDriverErrorType
InvalidSessionId -> Text
"Occurs if the given session id is not in the list of active sessions, meaning the session either does not exist or that it's not active"
WebDriverErrorType
JavascriptError -> Text
"An error occurred while executing JavaScript supplied by the user"
WebDriverErrorType
MoveTargetOutOfBounds -> Text
"The target for mouse interaction is not in the browser's viewport and cannot be brought into that viewport"
WebDriverErrorType
NoSuchAlert -> Text
"An attempt was made to operate on a modal dialog when one was not open"
WebDriverErrorType
NoSuchCookie -> Text
"No cookie matching the given path name was found amongst the associated cookies of session's current browsing context's active document"
WebDriverErrorType
NoSuchElement -> Text
"An element could not be located on the page using the given search parameters"
WebDriverErrorType
NoSuchFrame -> Text
"A command to switch to a frame could not be satisfied because the frame could not be found"
WebDriverErrorType
NoSuchWindow -> Text
"A command to switch to a window could not be satisfied because the window could not be found"
WebDriverErrorType
NoSuchShadowRoot -> Text
"The element does not have a shadow root"
WebDriverErrorType
ScriptTimeoutError -> Text
"A script did not complete before its timeout expired"
WebDriverErrorType
SessionNotCreated -> Text
"A new session could not be created"
WebDriverErrorType
StaleElementReference -> Text
"A command failed because the referenced element is no longer attached to the DOM"
WebDriverErrorType
DetachedShadowRoot -> Text
"A command failed because the referenced shadow root is no longer attached to the DOM"
WebDriverErrorType
Timeout -> Text
"An operation did not complete before its timeout expired"
WebDriverErrorType
UnableToSetCookie -> Text
"A command to set a cookie's value could not be satisfied"
WebDriverErrorType
UnableToCaptureScreen -> Text
"A screen capture was made impossible"
WebDriverErrorType
UnexpectedAlertOpen -> Text
"A modal dialog was open, blocking this operation"
WebDriverErrorType
UnknownCommand -> Text
"A command could not be executed because the remote end is not aware of it"
WebDriverErrorType
UnknownError -> Text
"An unknown error occurred in the remote end while processing the command"
WebDriverErrorType
UnknownMethod -> Text
"The requested command matched a known URL but did not match any method for that URL"
WebDriverErrorType
UnsupportedOperation -> Text
"Indicates that a command that should have executed properly cannot be supported for some reason"
data ErrorClassification =
NotAnError {ErrorClassification -> HttpResponse
httpResponse :: HttpResponse} |
UnrecognisedError {httpResponse :: HttpResponse} |
WebDriverError {
ErrorClassification -> WebDriverErrorType
error :: WebDriverErrorType,
ErrorClassification -> Text
description :: Text,
httpResponse :: HttpResponse
} deriving (ErrorClassification -> ErrorClassification -> Bool
(ErrorClassification -> ErrorClassification -> Bool)
-> (ErrorClassification -> ErrorClassification -> Bool)
-> Eq ErrorClassification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrorClassification -> ErrorClassification -> Bool
== :: ErrorClassification -> ErrorClassification -> Bool
$c/= :: ErrorClassification -> ErrorClassification -> Bool
/= :: ErrorClassification -> ErrorClassification -> Bool
Eq, Int -> ErrorClassification -> ShowS
[ErrorClassification] -> ShowS
ErrorClassification -> String
(Int -> ErrorClassification -> ShowS)
-> (ErrorClassification -> String)
-> ([ErrorClassification] -> ShowS)
-> Show ErrorClassification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrorClassification -> ShowS
showsPrec :: Int -> ErrorClassification -> ShowS
$cshow :: ErrorClassification -> String
show :: ErrorClassification -> String
$cshowList :: [ErrorClassification] -> ShowS
showList :: [ErrorClassification] -> ShowS
Show, Eq ErrorClassification
Eq ErrorClassification =>
(ErrorClassification -> ErrorClassification -> Ordering)
-> (ErrorClassification -> ErrorClassification -> Bool)
-> (ErrorClassification -> ErrorClassification -> Bool)
-> (ErrorClassification -> ErrorClassification -> Bool)
-> (ErrorClassification -> ErrorClassification -> Bool)
-> (ErrorClassification
-> ErrorClassification -> ErrorClassification)
-> (ErrorClassification
-> ErrorClassification -> ErrorClassification)
-> Ord ErrorClassification
ErrorClassification -> ErrorClassification -> Bool
ErrorClassification -> ErrorClassification -> Ordering
ErrorClassification -> ErrorClassification -> ErrorClassification
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ErrorClassification -> ErrorClassification -> Ordering
compare :: ErrorClassification -> ErrorClassification -> Ordering
$c< :: ErrorClassification -> ErrorClassification -> Bool
< :: ErrorClassification -> ErrorClassification -> Bool
$c<= :: ErrorClassification -> ErrorClassification -> Bool
<= :: ErrorClassification -> ErrorClassification -> Bool
$c> :: ErrorClassification -> ErrorClassification -> Bool
> :: ErrorClassification -> ErrorClassification -> Bool
$c>= :: ErrorClassification -> ErrorClassification -> Bool
>= :: ErrorClassification -> ErrorClassification -> Bool
$cmax :: ErrorClassification -> ErrorClassification -> ErrorClassification
max :: ErrorClassification -> ErrorClassification -> ErrorClassification
$cmin :: ErrorClassification -> ErrorClassification -> ErrorClassification
min :: ErrorClassification -> ErrorClassification -> ErrorClassification
Ord)
parseWebDriverError :: HttpResponse -> ErrorClassification
parseWebDriverError :: HttpResponse -> ErrorClassification
parseWebDriverError HttpResponse
resp =
case Value -> Maybe Text
getError HttpResponse
resp.body of
Maybe Text
Nothing -> HttpResponse -> ErrorClassification
NotAnError HttpResponse
resp
Just Text
err ->
case Text -> Either Text WebDriverErrorType
errorCodeToErrorType Text
err of
Right WebDriverErrorType
et -> WebDriverErrorType -> Text -> HttpResponse -> ErrorClassification
WebDriverError WebDriverErrorType
et (WebDriverErrorType -> Text
errorDescription WebDriverErrorType
et) HttpResponse
resp
Left Text
_ -> HttpResponse -> ErrorClassification
UnrecognisedError HttpResponse
resp
parseWebDriverErrorType :: HttpResponse -> Maybe WebDriverErrorType
parseWebDriverErrorType :: HttpResponse -> Maybe WebDriverErrorType
parseWebDriverErrorType HttpResponse
resp =
case HttpResponse -> ErrorClassification
parseWebDriverError HttpResponse
resp of
WebDriverError {WebDriverErrorType
error :: ErrorClassification -> WebDriverErrorType
error :: WebDriverErrorType
error} -> WebDriverErrorType -> Maybe WebDriverErrorType
forall a. a -> Maybe a
Just WebDriverErrorType
error
NotAnError {} -> Maybe WebDriverErrorType
forall a. Maybe a
Nothing
UnrecognisedError {} -> Maybe WebDriverErrorType
forall a. Maybe a
Nothing