{-# LANGUAGE ExistentialQuantification #-}
module Test.WebDriver.Commands
(
createSession, closeSession, sessions, getActualCaps
, openPage, forward, back, refresh
, getCurrentURL, getSource, getTitle, saveScreenshot, screenshot, screenshotBase64
, setImplicitWait, setScriptTimeout, setPageLoadTimeout
, Element(..), Selector(..)
, findElem, findElems, findElemFrom, findElemsFrom
, click, submit, getText
, sendKeys, sendRawKeys, clearInput
, attr, cssProp, elemPos, elemSize
, isSelected, isEnabled, isDisplayed
, tagName, activeElem, elemInfo
, (<==>), (</=>)
, executeJS, asyncJS
, JSArg(..)
, WindowHandle(..), currentWindow
, getCurrentWindow, closeWindow, windows, focusWindow, maximize
, getWindowSize, setWindowSize, getWindowPos, setWindowPos
, focusFrame, FrameSelector(..)
, Cookie(..), mkCookie
, cookies, setCookie, deleteCookie, deleteVisibleCookies, deleteCookieByName
, getAlertText, replyToAlert, acceptAlert, dismissAlert
, moveTo, moveToCenter, moveToFrom
, clickWith, MouseButton(..)
, mouseDown, mouseUp, withMouseDown, doubleClick
, WebStorageType(..), storageSize, getAllKeys, deleteAllKeys
, getKey, setKey, deleteKey
, ApplicationCacheStatus(..)
, getApplicationCacheStatus
, Orientation(..)
, getOrientation, setOrientation
, getLocation, setLocation
, touchClick, touchDown, touchUp, touchMove
, touchScroll, touchScrollFrom, touchDoubleClick
, touchLongClick, touchFlick, touchFlickFrom
, availableIMEEngines, activeIMEEngine, checkIMEActive
, activateIME, deactivateIME
, uploadFile, uploadRawFile, uploadZipEntry
, serverStatus
, getLogs, getLogTypes, LogType, LogEntry(..), LogLevel(..)
) where
import Codec.Archive.Zip
import Control.Applicative
import Control.Exception (SomeException)
import Control.Exception.Lifted (throwIO, handle)
import qualified Control.Exception.Lifted as L
import Control.Monad
import Control.Monad.Base
import Data.Aeson
import Data.Aeson.Types
import Data.ByteString.Base64.Lazy as B64
import Data.ByteString.Lazy as LBS (ByteString, writeFile)
import Data.CallStack
import qualified Data.Foldable as F
import Data.Maybe
import Data.String (fromString)
import Data.Text (Text, append, toUpper, toLower)
import qualified Data.Text as T
import qualified Data.Text.Lazy.Encoding as TL
import Data.Word
import Network.URI hiding (path)
import Test.WebDriver.Capabilities
import Test.WebDriver.Class
import Test.WebDriver.Commands.Internal
import Test.WebDriver.Cookies
import Test.WebDriver.Exceptions.Internal
import Test.WebDriver.JSON
import Test.WebDriver.Session
import Test.WebDriver.Utils (urlEncode)
import Prelude
createSession :: (HasCallStack, WebDriver wd) => Capabilities -> wd WDSession
createSession :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Capabilities -> wd WDSession
createSession Capabilities
caps = do
wd Value -> wd ()
forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn (wd Value -> wd ())
-> (Capabilities -> wd Value) -> Capabilities -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. wd Value -> wd Value
forall (m :: * -> *) a. WDSessionStateControl m => m a -> m a
withAuthHeaders (wd Value -> wd Value)
-> (Capabilities -> wd Value) -> Capabilities -> wd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd Value
forall a b.
(HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
forall (wd :: * -> *) a b.
(WebDriver wd, HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doCommand Method
methodPost Text
"/session" (Value -> wd Value)
-> (Capabilities -> Value) -> Capabilities -> wd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Capabilities -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"desiredCapabilities" (Capabilities -> wd ()) -> Capabilities -> wd ()
forall a b. (a -> b) -> a -> b
$ Capabilities
caps
wd WDSession
forall (m :: * -> *). WDSessionState m => m WDSession
getSession
sessions :: (HasCallStack, WebDriver wd) => wd [(SessionId, Capabilities)]
sessions :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd [(SessionId, Capabilities)]
sessions = do
[Value]
objs <- Method -> Text -> Value -> wd [Value]
forall a b.
(HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
forall (wd :: * -> *) a b.
(WebDriver wd, HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doCommand Method
methodGet Text
"/sessions" Value
Null
(Value -> wd (SessionId, Capabilities))
-> [Value] -> wd [(SessionId, Capabilities)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (String -> String -> String -> Value -> wd (SessionId, Capabilities)
forall (wd :: * -> *) a b.
(MonadBaseControl IO wd, FromJSON a, FromJSON b) =>
String -> String -> String -> Value -> wd (a, b)
parsePair String
"id" String
"capabilities" String
"sessions") [Value]
objs
getActualCaps :: (HasCallStack, WebDriver wd) => wd Capabilities
getActualCaps :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd Capabilities
getActualCaps = Method -> Text -> Value -> wd Capabilities
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"" Value
Null
closeSession :: (HasCallStack, WebDriver wd) => wd ()
closeSession :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
closeSession = do s :: WDSession
s@WDSession {} <- wd WDSession
forall (m :: * -> *). WDSessionState m => m WDSession
getSession
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"" Value
Null
WDSession -> wd ()
forall (m :: * -> *). WDSessionState m => WDSession -> m ()
putSession WDSession
s { wdSessId = Nothing }
setImplicitWait :: (HasCallStack, WebDriver wd) => Integer -> wd ()
setImplicitWait :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Integer -> wd ()
setImplicitWait Integer
ms =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/timeouts/implicit_wait" ([Pair] -> Value
object [Pair]
msField)
wd NoReturn -> (SomeException -> wd NoReturn) -> wd NoReturn
forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> (e -> m a) -> m a
`L.catch` \(SomeException
_ :: SomeException) ->
Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/timeouts" ([Pair] -> Value
object [Pair]
allFields)
where msField :: [Pair]
msField = [Key
"ms" Key -> Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Integer
ms]
allFields :: [Pair]
allFields = [Key
"type" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (String
"implicit" :: String)] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
msField
setScriptTimeout :: (HasCallStack, WebDriver wd) => Integer -> wd ()
setScriptTimeout :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Integer -> wd ()
setScriptTimeout Integer
ms =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/timeouts/async_script" ([Pair] -> Value
object [Pair]
msField)
wd NoReturn -> (SomeException -> wd NoReturn) -> wd NoReturn
forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> (e -> m a) -> m a
`L.catch` \( SomeException
_ :: SomeException) ->
Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/timeouts" ([Pair] -> Value
object [Pair]
allFields)
where msField :: [Pair]
msField = [Key
"ms" Key -> Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Integer
ms]
allFields :: [Pair]
allFields = [Key
"type" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (String
"script" :: String)] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
msField
setPageLoadTimeout :: (HasCallStack, WebDriver wd) => Integer -> wd ()
setPageLoadTimeout :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Integer -> wd ()
setPageLoadTimeout Integer
ms = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/timeouts" Value
params
where params :: Value
params = [Pair] -> Value
object [Key
"type" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (String
"page load" :: String)
,Key
"ms" Key -> Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Integer
ms ]
getCurrentURL :: (HasCallStack, WebDriver wd) => wd String
getCurrentURL :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd String
getCurrentURL = Method -> Text -> Value -> wd String
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/url" Value
Null
openPage :: (HasCallStack, WebDriver wd) => String -> wd ()
openPage :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd ()
openPage String
url
| String -> Bool
isURI String
url = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> (String -> wd NoReturn) -> String -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/url" (Value -> wd NoReturn)
-> (String -> Value) -> String -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"url" (String -> wd ()) -> String -> wd ()
forall a b. (a -> b) -> a -> b
$ String
url
| Bool
otherwise = InvalidURL -> wd ()
forall (m :: * -> *) e a. (MonadBase IO m, Exception e) => e -> m a
throwIO (InvalidURL -> wd ()) -> (String -> InvalidURL) -> String -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> InvalidURL
InvalidURL (String -> wd ()) -> String -> wd ()
forall a b. (a -> b) -> a -> b
$ String
url
forward :: (HasCallStack, WebDriver wd) => wd ()
forward :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
forward = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/forward" Value
Null
back :: (HasCallStack, WebDriver wd) => wd ()
back :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
back = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/back" Value
Null
refresh :: (HasCallStack, WebDriver wd) => wd ()
refresh :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
refresh = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/refresh" Value
Null
data JSArg = forall a. ToJSON a => JSArg a
instance ToJSON JSArg where
toJSON :: JSArg -> Value
toJSON (JSArg a
a) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a
executeJS :: (F.Foldable f, FromJSON a, WebDriver wd) => f JSArg -> Text -> wd a
executeJS :: forall (f :: * -> *) a (wd :: * -> *).
(Foldable f, FromJSON a, WebDriver wd) =>
f JSArg -> Text -> wd a
executeJS f JSArg
a Text
s = Value -> wd a
forall (wd :: * -> *) a.
(MonadBaseControl IO wd, FromJSON a) =>
Value -> wd a
fromJSON' (Value -> wd a) -> wd Value -> wd a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< wd Value
getResult
where
getResult :: wd Value
getResult = Method -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/execute" (Value -> wd Value)
-> (([JSArg], Text) -> Value) -> ([JSArg], Text) -> wd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> ([JSArg], Text) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"args", Text
"script") (([JSArg], Text) -> wd Value) -> ([JSArg], Text) -> wd Value
forall a b. (a -> b) -> a -> b
$ (f JSArg -> [JSArg]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList f JSArg
a,Text
s)
asyncJS :: (HasCallStack, F.Foldable f, FromJSON a, WebDriver wd) => f JSArg -> Text -> wd (Maybe a)
asyncJS :: forall (f :: * -> *) a (wd :: * -> *).
(HasCallStack, Foldable f, FromJSON a, WebDriver wd) =>
f JSArg -> Text -> wd (Maybe a)
asyncJS f JSArg
a Text
s = (FailedCommand -> wd (Maybe a)) -> wd (Maybe a) -> wd (Maybe a)
forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
(e -> m a) -> m a -> m a
handle FailedCommand -> wd (Maybe a)
forall {m :: * -> *} {a}.
MonadBase IO m =>
FailedCommand -> m (Maybe a)
timeout (wd (Maybe a) -> wd (Maybe a)) -> wd (Maybe a) -> wd (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> wd a -> wd (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> wd a
forall (wd :: * -> *) a.
(MonadBaseControl IO wd, FromJSON a) =>
Value -> wd a
fromJSON' (Value -> wd a) -> wd Value -> wd a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< wd Value
getResult)
where
getResult :: wd Value
getResult = Method -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/execute_async" (Value -> wd Value)
-> (([JSArg], Text) -> Value) -> ([JSArg], Text) -> wd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> ([JSArg], Text) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"args", Text
"script")
(([JSArg], Text) -> wd Value) -> ([JSArg], Text) -> wd Value
forall a b. (a -> b) -> a -> b
$ (f JSArg -> [JSArg]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList f JSArg
a,Text
s)
timeout :: FailedCommand -> m (Maybe a)
timeout (FailedCommand FailedCommandType
Timeout FailedCommandInfo
_) = Maybe a -> m (Maybe a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
timeout (FailedCommand FailedCommandType
ScriptTimeout FailedCommandInfo
_) = Maybe a -> m (Maybe a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
timeout FailedCommand
err = FailedCommand -> m (Maybe a)
forall (m :: * -> *) e a. (MonadBase IO m, Exception e) => e -> m a
throwIO FailedCommand
err
saveScreenshot :: (HasCallStack, WebDriver wd) => FilePath -> wd ()
saveScreenshot :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd ()
saveScreenshot String
path = wd ByteString
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshot wd ByteString -> (ByteString -> wd ()) -> wd ()
forall a b. wd a -> (a -> wd b) -> wd b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> wd ()
forall α. IO α -> wd α
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO () -> wd ()) -> (ByteString -> IO ()) -> ByteString -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString -> IO ()
LBS.writeFile String
path
screenshot :: (HasCallStack, WebDriver wd) => wd LBS.ByteString
screenshot :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshot = ByteString -> ByteString
B64.decodeLenient (ByteString -> ByteString) -> wd ByteString -> wd ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> wd ByteString
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshotBase64
screenshotBase64 :: (HasCallStack, WebDriver wd) => wd LBS.ByteString
screenshotBase64 :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshotBase64 = Text -> ByteString
TL.encodeUtf8 (Text -> ByteString) -> wd Text -> wd ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Method -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/screenshot" Value
Null
availableIMEEngines :: (HasCallStack, WebDriver wd) => wd [Text]
availableIMEEngines :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [Text]
availableIMEEngines = Method -> Text -> Value -> wd [Text]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/ime/available_engines" Value
Null
activeIMEEngine :: (HasCallStack, WebDriver wd) => wd Text
activeIMEEngine :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
activeIMEEngine = Method -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/ime/active_engine" Value
Null
checkIMEActive :: (HasCallStack, WebDriver wd) => wd Bool
checkIMEActive :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Bool
checkIMEActive = Method -> Text -> Value -> wd Bool
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/ime/activated" Value
Null
activateIME :: (HasCallStack, WebDriver wd) => Text -> wd ()
activateIME :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
activateIME = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> (Text -> wd NoReturn) -> Text -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/ime/activate" (Value -> wd NoReturn) -> (Text -> Value) -> Text -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"engine"
deactivateIME :: (HasCallStack, WebDriver wd) => wd ()
deactivateIME :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
deactivateIME = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/ime/deactivate" Value
Null
data FrameSelector = WithIndex Integer
| WithName Text
| WithElement Element
| DefaultFrame
deriving (FrameSelector -> FrameSelector -> Bool
(FrameSelector -> FrameSelector -> Bool)
-> (FrameSelector -> FrameSelector -> Bool) -> Eq FrameSelector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FrameSelector -> FrameSelector -> Bool
== :: FrameSelector -> FrameSelector -> Bool
$c/= :: FrameSelector -> FrameSelector -> Bool
/= :: FrameSelector -> FrameSelector -> Bool
Eq, Int -> FrameSelector -> ShowS
[FrameSelector] -> ShowS
FrameSelector -> String
(Int -> FrameSelector -> ShowS)
-> (FrameSelector -> String)
-> ([FrameSelector] -> ShowS)
-> Show FrameSelector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FrameSelector -> ShowS
showsPrec :: Int -> FrameSelector -> ShowS
$cshow :: FrameSelector -> String
show :: FrameSelector -> String
$cshowList :: [FrameSelector] -> ShowS
showList :: [FrameSelector] -> ShowS
Show, ReadPrec [FrameSelector]
ReadPrec FrameSelector
Int -> ReadS FrameSelector
ReadS [FrameSelector]
(Int -> ReadS FrameSelector)
-> ReadS [FrameSelector]
-> ReadPrec FrameSelector
-> ReadPrec [FrameSelector]
-> Read FrameSelector
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FrameSelector
readsPrec :: Int -> ReadS FrameSelector
$creadList :: ReadS [FrameSelector]
readList :: ReadS [FrameSelector]
$creadPrec :: ReadPrec FrameSelector
readPrec :: ReadPrec FrameSelector
$creadListPrec :: ReadPrec [FrameSelector]
readListPrec :: ReadPrec [FrameSelector]
Read)
instance ToJSON FrameSelector where
toJSON :: FrameSelector -> Value
toJSON FrameSelector
s = case FrameSelector
s of
WithIndex Integer
i -> Integer -> Value
forall a. ToJSON a => a -> Value
toJSON Integer
i
WithName Text
n -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
n
WithElement Element
e -> Element -> Value
forall a. ToJSON a => a -> Value
toJSON Element
e
FrameSelector
DefaultFrame -> Value
Null
focusFrame :: (HasCallStack, WebDriver wd) => FrameSelector -> wd ()
focusFrame :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
FrameSelector -> wd ()
focusFrame FrameSelector
s = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/frame" (Value -> wd NoReturn)
-> (FrameSelector -> Value) -> FrameSelector -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FrameSelector -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"id" (FrameSelector -> wd NoReturn) -> FrameSelector -> wd NoReturn
forall a b. (a -> b) -> a -> b
$ FrameSelector
s
getCurrentWindow :: (HasCallStack, WebDriver wd) => wd WindowHandle
getCurrentWindow :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd WindowHandle
getCurrentWindow = Method -> Text -> Value -> wd WindowHandle
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/window_handle" Value
Null
windows :: (HasCallStack, WebDriver wd) => wd [WindowHandle]
windows :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd [WindowHandle]
windows = Method -> Text -> Value -> wd [WindowHandle]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/window_handles" Value
Null
focusWindow :: (HasCallStack, WebDriver wd) => WindowHandle -> wd ()
focusWindow :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
focusWindow WindowHandle
w = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/window" (Value -> wd NoReturn)
-> (WindowHandle -> Value) -> WindowHandle -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> WindowHandle -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"handle" (WindowHandle -> wd NoReturn) -> WindowHandle -> wd NoReturn
forall a b. (a -> b) -> a -> b
$ WindowHandle
w
closeWindow :: (HasCallStack, WebDriver wd) => WindowHandle -> wd ()
closeWindow :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
closeWindow WindowHandle
w = do
WindowHandle
cw <- wd WindowHandle
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd WindowHandle
getCurrentWindow
WindowHandle -> wd ()
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
focusWindow WindowHandle
w
wd Value -> wd ()
forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn (wd Value -> wd ()) -> wd Value -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"/window" Value
Null
Bool -> wd () -> wd ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (WindowHandle
w WindowHandle -> WindowHandle -> Bool
forall a. Eq a => a -> a -> Bool
== WindowHandle
cw) (wd () -> wd ()) -> wd () -> wd ()
forall a b. (a -> b) -> a -> b
$ WindowHandle -> wd ()
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
focusWindow WindowHandle
cw
maximize :: (HasCallStack, WebDriver wd) => wd ()
maximize :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
maximize = wd Value -> wd ()
forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn (wd Value -> wd ()) -> wd Value -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> WindowHandle -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodPost WindowHandle
currentWindow Text
"/maximize" Value
Null
getWindowSize :: (HasCallStack, WebDriver wd) => wd (Word, Word)
getWindowSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd (Word, Word)
getWindowSize = Method -> WindowHandle -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodGet WindowHandle
currentWindow Text
"/size" Value
Null
wd Value -> (Value -> wd (Word, Word)) -> wd (Word, Word)
forall a b. wd a -> (a -> wd b) -> wd b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> String -> String -> Value -> wd (Word, Word)
forall (wd :: * -> *) a b.
(MonadBaseControl IO wd, FromJSON a, FromJSON b) =>
String -> String -> String -> Value -> wd (a, b)
parsePair String
"width" String
"height" String
"getWindowSize"
setWindowSize :: (HasCallStack, WebDriver wd) => (Word, Word) -> wd ()
setWindowSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Word, Word) -> wd ()
setWindowSize = wd Value -> wd ()
forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn (wd Value -> wd ())
-> ((Word, Word) -> wd Value) -> (Word, Word) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> WindowHandle -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodPost WindowHandle
currentWindow Text
"/size"
(Value -> wd Value)
-> ((Word, Word) -> Value) -> (Word, Word) -> wd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Word, Word) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"width", Text
"height")
getWindowPos :: (HasCallStack, WebDriver wd) => wd (Int, Int)
getWindowPos :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd (Int, Int)
getWindowPos = Method -> WindowHandle -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodGet WindowHandle
currentWindow Text
"/position" Value
Null
wd Value -> (Value -> wd (Int, Int)) -> wd (Int, Int)
forall a b. wd a -> (a -> wd b) -> wd b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> String -> String -> Value -> wd (Int, Int)
forall (wd :: * -> *) a b.
(MonadBaseControl IO wd, FromJSON a, FromJSON b) =>
String -> String -> String -> Value -> wd (a, b)
parsePair String
"x" String
"y" String
"getWindowPos"
setWindowPos :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
setWindowPos :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
setWindowPos = wd Value -> wd ()
forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn (wd Value -> wd ())
-> ((Int, Int) -> wd Value) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> WindowHandle -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodPost WindowHandle
currentWindow Text
"/position" (Value -> wd Value)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")
cookies :: (HasCallStack, WebDriver wd) => wd [Cookie]
cookies :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [Cookie]
cookies = Method -> Text -> Value -> wd [Cookie]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/cookie" Value
Null
setCookie :: (HasCallStack, WebDriver wd) => Cookie -> wd ()
setCookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Cookie -> wd ()
setCookie = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> (Cookie -> wd NoReturn) -> Cookie -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/cookie" (Value -> wd NoReturn)
-> (Cookie -> Value) -> Cookie -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Cookie -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"cookie"
deleteCookie :: (HasCallStack, WebDriver wd) => Cookie -> wd ()
deleteCookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Cookie -> wd ()
deleteCookie Cookie
c = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete (Text
"/cookie/" Text -> Text -> Text
`append` Text -> Text
urlEncode (Cookie -> Text
cookName Cookie
c)) Value
Null
deleteCookieByName :: (HasCallStack, WebDriver wd) => Text -> wd ()
deleteCookieByName :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
deleteCookieByName Text
n = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete (Text
"/cookie/" Text -> Text -> Text
`append` Text
n) Value
Null
deleteVisibleCookies :: (HasCallStack, WebDriver wd) => wd ()
deleteVisibleCookies :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
deleteVisibleCookies = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"/cookie" Value
Null
getSource :: (HasCallStack, WebDriver wd) => wd Text
getSource :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
getSource = Method -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/source" Value
Null
getTitle :: (HasCallStack, WebDriver wd) => wd Text
getTitle :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
getTitle = Method -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/title" Value
Null
data Selector = ById Text
| ByName Text
| ByClass Text
| ByTag Text
| ByLinkText Text
| ByPartialLinkText Text
| ByCSS Text
| ByXPath Text
deriving (Selector -> Selector -> Bool
(Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool) -> Eq Selector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Selector -> Selector -> Bool
== :: Selector -> Selector -> Bool
$c/= :: Selector -> Selector -> Bool
/= :: Selector -> Selector -> Bool
Eq, Int -> Selector -> ShowS
[Selector] -> ShowS
Selector -> String
(Int -> Selector -> ShowS)
-> (Selector -> String) -> ([Selector] -> ShowS) -> Show Selector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Selector -> ShowS
showsPrec :: Int -> Selector -> ShowS
$cshow :: Selector -> String
show :: Selector -> String
$cshowList :: [Selector] -> ShowS
showList :: [Selector] -> ShowS
Show, Eq Selector
Eq Selector =>
(Selector -> Selector -> Ordering)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool)
-> (Selector -> Selector -> Selector)
-> (Selector -> Selector -> Selector)
-> Ord Selector
Selector -> Selector -> Bool
Selector -> Selector -> Ordering
Selector -> Selector -> Selector
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 :: Selector -> Selector -> Ordering
compare :: Selector -> Selector -> Ordering
$c< :: Selector -> Selector -> Bool
< :: Selector -> Selector -> Bool
$c<= :: Selector -> Selector -> Bool
<= :: Selector -> Selector -> Bool
$c> :: Selector -> Selector -> Bool
> :: Selector -> Selector -> Bool
$c>= :: Selector -> Selector -> Bool
>= :: Selector -> Selector -> Bool
$cmax :: Selector -> Selector -> Selector
max :: Selector -> Selector -> Selector
$cmin :: Selector -> Selector -> Selector
min :: Selector -> Selector -> Selector
Ord)
instance ToJSON Selector where
toJSON :: Selector -> Value
toJSON Selector
s = case Selector
s of
ById Text
t -> Text -> Text -> Value
selector Text
"id" Text
t
ByName Text
t -> Text -> Text -> Value
selector Text
"name" Text
t
ByClass Text
t -> Text -> Text -> Value
selector Text
"class name" Text
t
ByTag Text
t -> Text -> Text -> Value
selector Text
"tag name" Text
t
ByLinkText Text
t -> Text -> Text -> Value
selector Text
"link text" Text
t
ByPartialLinkText Text
t -> Text -> Text -> Value
selector Text
"partial link text" Text
t
ByCSS Text
t -> Text -> Text -> Value
selector Text
"css selector" Text
t
ByXPath Text
t -> Text -> Text -> Value
selector Text
"xpath" Text
t
where
selector :: Text -> Text -> Value
selector :: Text -> Text -> Value
selector Text
sn Text
t = [Pair] -> Value
object [Key
"using" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
sn, Key
"value" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
t]
findElem :: (HasCallStack, WebDriver wd) => Selector -> wd Element
findElem :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Selector -> wd Element
findElem = Method -> Text -> Selector -> wd Element
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/element"
findElems :: (HasCallStack, WebDriver wd) => Selector -> wd [Element]
findElems :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Selector -> wd [Element]
findElems = Method -> Text -> Selector -> wd [Element]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/elements"
activeElem :: (HasCallStack, WebDriver wd) => wd Element
activeElem :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Element
activeElem = Method -> Text -> Value -> wd Element
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/element/active" Value
Null
findElemFrom :: (HasCallStack, WebDriver wd) => Element -> Selector -> wd Element
findElemFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Selector -> wd Element
findElemFrom Element
e = Method -> Element -> Text -> Selector -> wd Element
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/element"
findElemsFrom :: (HasCallStack, WebDriver wd) => Element -> Selector -> wd [Element]
findElemsFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Selector -> wd [Element]
findElemsFrom Element
e = Method -> Element -> Text -> Selector -> wd [Element]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/elements"
elemInfo :: (HasCallStack, WebDriver wd) => Element -> wd Value
elemInfo :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Value
elemInfo Element
e = Method -> Element -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"" Value
Null
{-# DEPRECATED elemInfo "This command does not work with Marionette (Firefox) driver, and is likely to be completely removed in Selenium 4" #-}
click :: (HasCallStack, WebDriver wd) => Element -> wd ()
click :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
click Element
e = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Element -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/click" Value
Null
submit :: (HasCallStack, WebDriver wd) => Element -> wd ()
submit :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
submit Element
e = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Element -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/submit" Value
Null
getText :: (HasCallStack, WebDriver wd) => Element -> wd Text
getText :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Text
getText Element
e = Method -> Element -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/text" Value
Null
sendKeys :: (HasCallStack, WebDriver wd) => Text -> Element -> wd ()
sendKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> Element -> wd ()
sendKeys Text
t Element
e = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ([Text] -> wd NoReturn) -> [Text] -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Element -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/value" (Value -> wd NoReturn)
-> ([Text] -> Value) -> [Text] -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"value" ([Text] -> wd ()) -> [Text] -> wd ()
forall a b. (a -> b) -> a -> b
$ [Text
t]
sendRawKeys :: (HasCallStack, WebDriver wd) => Text -> wd ()
sendRawKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
sendRawKeys Text
t = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ([Text] -> wd NoReturn) -> [Text] -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/keys" (Value -> wd NoReturn)
-> ([Text] -> Value) -> [Text] -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"value" ([Text] -> wd ()) -> [Text] -> wd ()
forall a b. (a -> b) -> a -> b
$ [Text
t]
tagName :: (HasCallStack, WebDriver wd) => Element -> wd Text
tagName :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Text
tagName Element
e = Method -> Element -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/name" Value
Null
clearInput :: (HasCallStack, WebDriver wd) => Element -> wd ()
clearInput :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
clearInput Element
e = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Element -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/clear" Value
Null
isSelected :: (HasCallStack, WebDriver wd) => Element -> wd Bool
isSelected :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Bool
isSelected Element
e = Method -> Element -> Text -> Value -> wd Bool
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/selected" Value
Null
isEnabled :: (HasCallStack, WebDriver wd) => Element -> wd Bool
isEnabled :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Bool
isEnabled Element
e = Method -> Element -> Text -> Value -> wd Bool
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/enabled" Value
Null
isDisplayed :: (HasCallStack, WebDriver wd) => Element -> wd Bool
isDisplayed :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Bool
isDisplayed Element
e = Method -> Element -> Text -> Value -> wd Bool
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/displayed" Value
Null
attr :: (HasCallStack, WebDriver wd) => Element -> Text -> wd (Maybe Text)
attr :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Text -> wd (Maybe Text)
attr Element
e Text
t = Method -> Element -> Text -> Value -> wd (Maybe Text)
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e (Text
"/attribute/" Text -> Text -> Text
`append` Text -> Text
urlEncode Text
t) Value
Null
cssProp :: (HasCallStack, WebDriver wd) => Element -> Text -> wd (Maybe Text)
cssProp :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Text -> wd (Maybe Text)
cssProp Element
e Text
t = Method -> Element -> Text -> Value -> wd (Maybe Text)
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e (Text
"/css/" Text -> Text -> Text
`append` Text -> Text
urlEncode Text
t) Value
Null
elemPos :: (HasCallStack, WebDriver wd) => Element -> wd (Float, Float)
elemPos :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd (Float, Float)
elemPos Element
e = Method -> Element -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/location" Value
Null wd Value -> (Value -> wd (Float, Float)) -> wd (Float, Float)
forall a b. wd a -> (a -> wd b) -> wd b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> String -> String -> Value -> wd (Float, Float)
forall (wd :: * -> *) a b.
(MonadBaseControl IO wd, FromJSON a, FromJSON b) =>
String -> String -> String -> Value -> wd (a, b)
parsePair String
"x" String
"y" String
"elemPos"
elemSize :: (HasCallStack, WebDriver wd) => Element -> wd (Float, Float)
elemSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd (Float, Float)
elemSize Element
e = Method -> Element -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e Text
"/size" Value
Null
wd Value -> (Value -> wd (Float, Float)) -> wd (Float, Float)
forall a b. wd a -> (a -> wd b) -> wd b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> String -> String -> Value -> wd (Float, Float)
forall (wd :: * -> *) a b.
(MonadBaseControl IO wd, FromJSON a, FromJSON b) =>
String -> String -> String -> Value -> wd (a, b)
parsePair String
"width" String
"height" String
"elemSize"
infix 4 <==>
(<==>) :: (HasCallStack, WebDriver wd) => Element -> Element -> wd Bool
Element
e1 <==> :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Element -> wd Bool
<==> (Element Text
e2) = Method -> Element -> Text -> Value -> wd Bool
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodGet Element
e1 (Text
"/equals/" Text -> Text -> Text
`append` Text -> Text
urlEncode Text
e2) Value
Null
infix 4 </=>
(</=>) :: (HasCallStack, WebDriver wd) => Element -> Element -> wd Bool
Element
e1 </=> :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Element -> wd Bool
</=> Element
e2 = Bool -> Bool
not (Bool -> Bool) -> wd Bool -> wd Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Element
e1 Element -> Element -> wd Bool
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Element -> wd Bool
<==> Element
e2)
data Orientation = Landscape | Portrait
deriving (Orientation -> Orientation -> Bool
(Orientation -> Orientation -> Bool)
-> (Orientation -> Orientation -> Bool) -> Eq Orientation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Orientation -> Orientation -> Bool
== :: Orientation -> Orientation -> Bool
$c/= :: Orientation -> Orientation -> Bool
/= :: Orientation -> Orientation -> Bool
Eq, Int -> Orientation -> ShowS
[Orientation] -> ShowS
Orientation -> String
(Int -> Orientation -> ShowS)
-> (Orientation -> String)
-> ([Orientation] -> ShowS)
-> Show Orientation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Orientation -> ShowS
showsPrec :: Int -> Orientation -> ShowS
$cshow :: Orientation -> String
show :: Orientation -> String
$cshowList :: [Orientation] -> ShowS
showList :: [Orientation] -> ShowS
Show, Eq Orientation
Eq Orientation =>
(Orientation -> Orientation -> Ordering)
-> (Orientation -> Orientation -> Bool)
-> (Orientation -> Orientation -> Bool)
-> (Orientation -> Orientation -> Bool)
-> (Orientation -> Orientation -> Bool)
-> (Orientation -> Orientation -> Orientation)
-> (Orientation -> Orientation -> Orientation)
-> Ord Orientation
Orientation -> Orientation -> Bool
Orientation -> Orientation -> Ordering
Orientation -> Orientation -> Orientation
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 :: Orientation -> Orientation -> Ordering
compare :: Orientation -> Orientation -> Ordering
$c< :: Orientation -> Orientation -> Bool
< :: Orientation -> Orientation -> Bool
$c<= :: Orientation -> Orientation -> Bool
<= :: Orientation -> Orientation -> Bool
$c> :: Orientation -> Orientation -> Bool
> :: Orientation -> Orientation -> Bool
$c>= :: Orientation -> Orientation -> Bool
>= :: Orientation -> Orientation -> Bool
$cmax :: Orientation -> Orientation -> Orientation
max :: Orientation -> Orientation -> Orientation
$cmin :: Orientation -> Orientation -> Orientation
min :: Orientation -> Orientation -> Orientation
Ord, Orientation
Orientation -> Orientation -> Bounded Orientation
forall a. a -> a -> Bounded a
$cminBound :: Orientation
minBound :: Orientation
$cmaxBound :: Orientation
maxBound :: Orientation
Bounded, Int -> Orientation
Orientation -> Int
Orientation -> [Orientation]
Orientation -> Orientation
Orientation -> Orientation -> [Orientation]
Orientation -> Orientation -> Orientation -> [Orientation]
(Orientation -> Orientation)
-> (Orientation -> Orientation)
-> (Int -> Orientation)
-> (Orientation -> Int)
-> (Orientation -> [Orientation])
-> (Orientation -> Orientation -> [Orientation])
-> (Orientation -> Orientation -> [Orientation])
-> (Orientation -> Orientation -> Orientation -> [Orientation])
-> Enum Orientation
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 :: Orientation -> Orientation
succ :: Orientation -> Orientation
$cpred :: Orientation -> Orientation
pred :: Orientation -> Orientation
$ctoEnum :: Int -> Orientation
toEnum :: Int -> Orientation
$cfromEnum :: Orientation -> Int
fromEnum :: Orientation -> Int
$cenumFrom :: Orientation -> [Orientation]
enumFrom :: Orientation -> [Orientation]
$cenumFromThen :: Orientation -> Orientation -> [Orientation]
enumFromThen :: Orientation -> Orientation -> [Orientation]
$cenumFromTo :: Orientation -> Orientation -> [Orientation]
enumFromTo :: Orientation -> Orientation -> [Orientation]
$cenumFromThenTo :: Orientation -> Orientation -> Orientation -> [Orientation]
enumFromThenTo :: Orientation -> Orientation -> Orientation -> [Orientation]
Enum)
instance ToJSON Orientation where
toJSON :: Orientation -> Value
toJSON = Text -> Value
String (Text -> Value) -> (Orientation -> Text) -> Orientation -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
toUpper (Text -> Text) -> (Orientation -> Text) -> Orientation -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString (String -> Text) -> (Orientation -> String) -> Orientation -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Orientation -> String
forall a. Show a => a -> String
show
instance FromJSON Orientation where
parseJSON :: Value -> Parser Orientation
parseJSON (String Text
jStr) = case Text -> Text
toLower Text
jStr of
Text
"landscape" -> Orientation -> Parser Orientation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
Landscape
Text
"portrait" -> Orientation -> Parser Orientation
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
Portrait
Text
err -> String -> Parser Orientation
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Orientation) -> String -> Parser Orientation
forall a b. (a -> b) -> a -> b
$ String
"Invalid Orientation string " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
err
parseJSON Value
v = String -> Value -> Parser Orientation
forall a. String -> Value -> Parser a
typeMismatch String
"Orientation" Value
v
getOrientation :: (HasCallStack, WebDriver wd) => wd Orientation
getOrientation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd Orientation
getOrientation = Method -> Text -> Value -> wd Orientation
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/orientation" Value
Null
setOrientation :: (HasCallStack, WebDriver wd) => Orientation -> wd ()
setOrientation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Orientation -> wd ()
setOrientation = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> (Orientation -> wd NoReturn) -> Orientation -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/orientation" (Value -> wd NoReturn)
-> (Orientation -> Value) -> Orientation -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Orientation -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"orientation"
getAlertText :: (HasCallStack, WebDriver wd) => wd Text
getAlertText :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
getAlertText = Method -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/alert_text" Value
Null
replyToAlert :: (HasCallStack, WebDriver wd) => Text -> wd ()
replyToAlert :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
replyToAlert = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> (Text -> wd NoReturn) -> Text -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/alert_text" (Value -> wd NoReturn) -> (Text -> Value) -> Text -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"text"
acceptAlert :: (HasCallStack, WebDriver wd) => wd ()
acceptAlert :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
acceptAlert = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/accept_alert" Value
Null
dismissAlert :: (HasCallStack, WebDriver wd) => wd ()
dismissAlert :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
dismissAlert = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/dismiss_alert" Value
Null
moveTo :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
moveTo :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
moveTo = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Int, Int) -> wd NoReturn) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/moveto" (Value -> wd NoReturn)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"xoffset",Text
"yoffset")
moveToCenter :: (HasCallStack, WebDriver wd) => Element -> wd ()
moveToCenter :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
moveToCenter (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> (Text -> wd NoReturn) -> Text -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/moveto" (Value -> wd NoReturn) -> (Text -> Value) -> Text -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"element" (Text -> wd ()) -> Text -> wd ()
forall a b. (a -> b) -> a -> b
$ Text
e
moveToFrom :: (HasCallStack, WebDriver wd) => (Int, Int) -> Element -> wd ()
moveToFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> Element -> wd ()
moveToFrom (Int
x,Int
y) (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Text, Int, Int) -> wd NoReturn) -> (Text, Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/moveto"
(Value -> wd NoReturn)
-> ((Text, Int, Int) -> Value) -> (Text, Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text, Text) -> (Text, Int, Int) -> Value
forall a b c.
(ToJSON a, ToJSON b, ToJSON c) =>
(Text, Text, Text) -> (a, b, c) -> Value
triple (Text
"element",Text
"xoffset",Text
"yoffset") ((Text, Int, Int) -> wd ()) -> (Text, Int, Int) -> wd ()
forall a b. (a -> b) -> a -> b
$ (Text
e,Int
x,Int
y)
data MouseButton = LeftButton | MiddleButton | RightButton
deriving (MouseButton -> MouseButton -> Bool
(MouseButton -> MouseButton -> Bool)
-> (MouseButton -> MouseButton -> Bool) -> Eq MouseButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MouseButton -> MouseButton -> Bool
== :: MouseButton -> MouseButton -> Bool
$c/= :: MouseButton -> MouseButton -> Bool
/= :: MouseButton -> MouseButton -> Bool
Eq, Int -> MouseButton -> ShowS
[MouseButton] -> ShowS
MouseButton -> String
(Int -> MouseButton -> ShowS)
-> (MouseButton -> String)
-> ([MouseButton] -> ShowS)
-> Show MouseButton
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MouseButton -> ShowS
showsPrec :: Int -> MouseButton -> ShowS
$cshow :: MouseButton -> String
show :: MouseButton -> String
$cshowList :: [MouseButton] -> ShowS
showList :: [MouseButton] -> ShowS
Show, Eq MouseButton
Eq MouseButton =>
(MouseButton -> MouseButton -> Ordering)
-> (MouseButton -> MouseButton -> Bool)
-> (MouseButton -> MouseButton -> Bool)
-> (MouseButton -> MouseButton -> Bool)
-> (MouseButton -> MouseButton -> Bool)
-> (MouseButton -> MouseButton -> MouseButton)
-> (MouseButton -> MouseButton -> MouseButton)
-> Ord MouseButton
MouseButton -> MouseButton -> Bool
MouseButton -> MouseButton -> Ordering
MouseButton -> MouseButton -> MouseButton
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 :: MouseButton -> MouseButton -> Ordering
compare :: MouseButton -> MouseButton -> Ordering
$c< :: MouseButton -> MouseButton -> Bool
< :: MouseButton -> MouseButton -> Bool
$c<= :: MouseButton -> MouseButton -> Bool
<= :: MouseButton -> MouseButton -> Bool
$c> :: MouseButton -> MouseButton -> Bool
> :: MouseButton -> MouseButton -> Bool
$c>= :: MouseButton -> MouseButton -> Bool
>= :: MouseButton -> MouseButton -> Bool
$cmax :: MouseButton -> MouseButton -> MouseButton
max :: MouseButton -> MouseButton -> MouseButton
$cmin :: MouseButton -> MouseButton -> MouseButton
min :: MouseButton -> MouseButton -> MouseButton
Ord, MouseButton
MouseButton -> MouseButton -> Bounded MouseButton
forall a. a -> a -> Bounded a
$cminBound :: MouseButton
minBound :: MouseButton
$cmaxBound :: MouseButton
maxBound :: MouseButton
Bounded, Int -> MouseButton
MouseButton -> Int
MouseButton -> [MouseButton]
MouseButton -> MouseButton
MouseButton -> MouseButton -> [MouseButton]
MouseButton -> MouseButton -> MouseButton -> [MouseButton]
(MouseButton -> MouseButton)
-> (MouseButton -> MouseButton)
-> (Int -> MouseButton)
-> (MouseButton -> Int)
-> (MouseButton -> [MouseButton])
-> (MouseButton -> MouseButton -> [MouseButton])
-> (MouseButton -> MouseButton -> [MouseButton])
-> (MouseButton -> MouseButton -> MouseButton -> [MouseButton])
-> Enum MouseButton
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 :: MouseButton -> MouseButton
succ :: MouseButton -> MouseButton
$cpred :: MouseButton -> MouseButton
pred :: MouseButton -> MouseButton
$ctoEnum :: Int -> MouseButton
toEnum :: Int -> MouseButton
$cfromEnum :: MouseButton -> Int
fromEnum :: MouseButton -> Int
$cenumFrom :: MouseButton -> [MouseButton]
enumFrom :: MouseButton -> [MouseButton]
$cenumFromThen :: MouseButton -> MouseButton -> [MouseButton]
enumFromThen :: MouseButton -> MouseButton -> [MouseButton]
$cenumFromTo :: MouseButton -> MouseButton -> [MouseButton]
enumFromTo :: MouseButton -> MouseButton -> [MouseButton]
$cenumFromThenTo :: MouseButton -> MouseButton -> MouseButton -> [MouseButton]
enumFromThenTo :: MouseButton -> MouseButton -> MouseButton -> [MouseButton]
Enum)
instance ToJSON MouseButton where
toJSON :: MouseButton -> Value
toJSON = Int -> Value
forall a. ToJSON a => a -> Value
toJSON (Int -> Value) -> (MouseButton -> Int) -> MouseButton -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MouseButton -> Int
forall a. Enum a => a -> Int
fromEnum
instance FromJSON MouseButton where
parseJSON :: Value -> Parser MouseButton
parseJSON Value
v = do
Integer
n <- Value -> Parser Integer
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
case Integer
n :: Integer of
Integer
0 -> MouseButton -> Parser MouseButton
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return MouseButton
LeftButton
Integer
1 -> MouseButton -> Parser MouseButton
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return MouseButton
MiddleButton
Integer
2 -> MouseButton -> Parser MouseButton
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return MouseButton
RightButton
Integer
err -> String -> Parser MouseButton
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser MouseButton) -> String -> Parser MouseButton
forall a b. (a -> b) -> a -> b
$ String
"Invalid JSON for MouseButton: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
err
clickWith :: (HasCallStack, WebDriver wd) => MouseButton -> wd ()
clickWith :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
MouseButton -> wd ()
clickWith = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> (MouseButton -> wd NoReturn) -> MouseButton -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/click" (Value -> wd NoReturn)
-> (MouseButton -> Value) -> MouseButton -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> MouseButton -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"button"
withMouseDown :: (HasCallStack, WebDriver wd) => wd a -> wd a
withMouseDown :: forall (wd :: * -> *) a.
(HasCallStack, WebDriver wd) =>
wd a -> wd a
withMouseDown wd a
wd = wd ()
forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseDown wd () -> wd a -> wd a
forall a b. wd a -> wd b -> wd b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> wd a
wd wd a -> wd () -> wd a
forall a b. wd a -> wd b -> wd a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* wd ()
forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseUp
mouseDown :: (HasCallStack, WebDriver wd) => wd ()
mouseDown :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseDown = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/buttondown" Value
Null
mouseUp :: (HasCallStack, WebDriver wd) => wd ()
mouseUp :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseUp = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/buttonup" Value
Null
doubleClick :: (HasCallStack, WebDriver wd) => wd ()
doubleClick :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
doubleClick = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/doubleclick" Value
Null
touchClick :: (HasCallStack, WebDriver wd) => Element -> wd ()
touchClick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
touchClick (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> (Text -> wd NoReturn) -> Text -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/click" (Value -> wd NoReturn) -> (Text -> Value) -> Text -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"element" (Text -> wd ()) -> Text -> wd ()
forall a b. (a -> b) -> a -> b
$ Text
e
touchDown :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchDown :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchDown = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Int, Int) -> wd NoReturn) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/down" (Value -> wd NoReturn)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")
touchUp :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchUp :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchUp = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Int, Int) -> wd NoReturn) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/up" (Value -> wd NoReturn)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")
touchMove :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchMove :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchMove = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Int, Int) -> wd NoReturn) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/move" (Value -> wd NoReturn)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")
touchScroll :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchScroll :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchScroll = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Int, Int) -> wd NoReturn) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/scroll" (Value -> wd NoReturn)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"xoffset",Text
"yoffset")
touchScrollFrom :: (HasCallStack, WebDriver wd) => (Int, Int) -> Element -> wd ()
touchScrollFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> Element -> wd ()
touchScrollFrom (Int
x, Int
y) (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
(wd NoReturn -> wd ())
-> ((Int, Int, Text) -> wd NoReturn) -> (Int, Int, Text) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/scroll"
(Value -> wd NoReturn)
-> ((Int, Int, Text) -> Value) -> (Int, Int, Text) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text, Text) -> (Int, Int, Text) -> Value
forall a b c.
(ToJSON a, ToJSON b, ToJSON c) =>
(Text, Text, Text) -> (a, b, c) -> Value
triple (Text
"xoffset", Text
"yoffset", Text
"element")
((Int, Int, Text) -> wd ()) -> (Int, Int, Text) -> wd ()
forall a b. (a -> b) -> a -> b
$ (Int
x, Int
y, Text
e)
touchDoubleClick :: (HasCallStack, WebDriver wd) => Element -> wd ()
touchDoubleClick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
touchDoubleClick (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
(wd NoReturn -> wd ()) -> (Text -> wd NoReturn) -> Text -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/doubleclick"
(Value -> wd NoReturn) -> (Text -> Value) -> Text -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"element" (Text -> wd ()) -> Text -> wd ()
forall a b. (a -> b) -> a -> b
$ Text
e
touchLongClick :: (HasCallStack, WebDriver wd) => Element -> wd ()
touchLongClick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
touchLongClick (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
(wd NoReturn -> wd ()) -> (Text -> wd NoReturn) -> Text -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/longclick"
(Value -> wd NoReturn) -> (Text -> Value) -> Text -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"element" (Text -> wd ()) -> Text -> wd ()
forall a b. (a -> b) -> a -> b
$ Text
e
touchFlick :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchFlick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchFlick =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
(wd NoReturn -> wd ())
-> ((Int, Int) -> wd NoReturn) -> (Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/flick"
(Value -> wd NoReturn)
-> ((Int, Int) -> Value) -> (Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> (Int, Int) -> Value
forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"xSpeed", Text
"ySpeed")
touchFlickFrom :: (HasCallStack, WebDriver wd) =>
Int
-> (Int, Int)
-> Element
-> wd ()
touchFlickFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Int -> (Int, Int) -> Element -> wd ()
touchFlickFrom Int
s (Int
x,Int
y) (Element Text
e) =
wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
(wd NoReturn -> wd ())
-> ([Pair] -> wd NoReturn) -> [Pair] -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/flick" (Value -> wd NoReturn)
-> ([Pair] -> Value) -> [Pair] -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
object ([Pair] -> wd ()) -> [Pair] -> wd ()
forall a b. (a -> b) -> a -> b
$
[Key
"xoffset" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
x
,Key
"yoffset" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
y
,Key
"speed" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
s
,Key
"element" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
e
]
getLocation :: (HasCallStack, WebDriver wd) => wd (Int, Int, Int)
getLocation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd (Int, Int, Int)
getLocation = Method -> Text -> Value -> wd Value
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/location" Value
Null
wd Value -> (Value -> wd (Int, Int, Int)) -> wd (Int, Int, Int)
forall a b. wd a -> (a -> wd b) -> wd b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> String -> String -> String -> Value -> wd (Int, Int, Int)
forall (wd :: * -> *) a b c.
(MonadBaseControl IO wd, FromJSON a, FromJSON b, FromJSON c) =>
String -> String -> String -> String -> Value -> wd (a, b, c)
parseTriple String
"latitude" String
"longitude" String
"altitude" String
"getLocation"
setLocation :: (HasCallStack, WebDriver wd) => (Int, Int, Int) -> wd ()
setLocation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int, Int) -> wd ()
setLocation = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ())
-> ((Int, Int, Int) -> wd NoReturn) -> (Int, Int, Int) -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/location"
(Value -> wd NoReturn)
-> ((Int, Int, Int) -> Value) -> (Int, Int, Int) -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text, Text) -> (Int, Int, Int) -> Value
forall a b c.
(ToJSON a, ToJSON b, ToJSON c) =>
(Text, Text, Text) -> (a, b, c) -> Value
triple (Text
"latitude",
Text
"longitude",
Text
"altitude")
uploadFile :: (HasCallStack, WebDriver wd) => FilePath -> wd ()
uploadFile :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd ()
uploadFile String
path = Entry -> wd ()
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Entry -> wd ()
uploadZipEntry (Entry -> wd ()) -> wd Entry -> wd ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO Entry -> wd Entry
forall α. IO α -> wd α
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase ([ZipOption] -> String -> IO Entry
readEntry [] String
path)
uploadRawFile :: (HasCallStack, WebDriver wd) =>
FilePath
-> Integer
-> LBS.ByteString
-> wd ()
uploadRawFile :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> Integer -> ByteString -> wd ()
uploadRawFile String
path Integer
t ByteString
str = Entry -> wd ()
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Entry -> wd ()
uploadZipEntry (String -> Integer -> ByteString -> Entry
toEntry String
path Integer
t ByteString
str)
uploadZipEntry :: (HasCallStack, WebDriver wd) => Entry -> wd ()
uploadZipEntry :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Entry -> wd ()
uploadZipEntry = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> (Entry -> wd NoReturn) -> Entry -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/file" (Value -> wd NoReturn) -> (Entry -> Value) -> Entry -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"file"
(Text -> Value) -> (Entry -> Text) -> Entry -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 (ByteString -> Text) -> (Entry -> ByteString) -> Entry -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64.encode (ByteString -> ByteString)
-> (Entry -> ByteString) -> Entry -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> ByteString
fromArchive (Archive -> ByteString)
-> (Entry -> Archive) -> Entry -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entry -> Archive -> Archive
`addEntryToArchive` Archive
emptyArchive)
storageSize :: (HasCallStack, WebDriver wd) => WebStorageType -> wd Integer
storageSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> wd Integer
storageSize WebStorageType
s = Method -> WebStorageType -> Text -> Value -> wd Integer
forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodGet WebStorageType
s Text
"/size" Value
Null
getAllKeys :: (HasCallStack, WebDriver wd) => WebStorageType -> wd [Text]
getAllKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> wd [Text]
getAllKeys WebStorageType
s = Method -> WebStorageType -> Text -> Value -> wd [Text]
forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodGet WebStorageType
s Text
"" Value
Null
deleteAllKeys :: (HasCallStack, WebDriver wd) => WebStorageType -> wd ()
deleteAllKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> wd ()
deleteAllKeys WebStorageType
s = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> WebStorageType -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodDelete WebStorageType
s Text
"" Value
Null
data WebStorageType = LocalStorage | SessionStorage
deriving (WebStorageType -> WebStorageType -> Bool
(WebStorageType -> WebStorageType -> Bool)
-> (WebStorageType -> WebStorageType -> Bool) -> Eq WebStorageType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebStorageType -> WebStorageType -> Bool
== :: WebStorageType -> WebStorageType -> Bool
$c/= :: WebStorageType -> WebStorageType -> Bool
/= :: WebStorageType -> WebStorageType -> Bool
Eq, Int -> WebStorageType -> ShowS
[WebStorageType] -> ShowS
WebStorageType -> String
(Int -> WebStorageType -> ShowS)
-> (WebStorageType -> String)
-> ([WebStorageType] -> ShowS)
-> Show WebStorageType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WebStorageType -> ShowS
showsPrec :: Int -> WebStorageType -> ShowS
$cshow :: WebStorageType -> String
show :: WebStorageType -> String
$cshowList :: [WebStorageType] -> ShowS
showList :: [WebStorageType] -> ShowS
Show, Eq WebStorageType
Eq WebStorageType =>
(WebStorageType -> WebStorageType -> Ordering)
-> (WebStorageType -> WebStorageType -> Bool)
-> (WebStorageType -> WebStorageType -> Bool)
-> (WebStorageType -> WebStorageType -> Bool)
-> (WebStorageType -> WebStorageType -> Bool)
-> (WebStorageType -> WebStorageType -> WebStorageType)
-> (WebStorageType -> WebStorageType -> WebStorageType)
-> Ord WebStorageType
WebStorageType -> WebStorageType -> Bool
WebStorageType -> WebStorageType -> Ordering
WebStorageType -> WebStorageType -> WebStorageType
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 :: WebStorageType -> WebStorageType -> Ordering
compare :: WebStorageType -> WebStorageType -> Ordering
$c< :: WebStorageType -> WebStorageType -> Bool
< :: WebStorageType -> WebStorageType -> Bool
$c<= :: WebStorageType -> WebStorageType -> Bool
<= :: WebStorageType -> WebStorageType -> Bool
$c> :: WebStorageType -> WebStorageType -> Bool
> :: WebStorageType -> WebStorageType -> Bool
$c>= :: WebStorageType -> WebStorageType -> Bool
>= :: WebStorageType -> WebStorageType -> Bool
$cmax :: WebStorageType -> WebStorageType -> WebStorageType
max :: WebStorageType -> WebStorageType -> WebStorageType
$cmin :: WebStorageType -> WebStorageType -> WebStorageType
min :: WebStorageType -> WebStorageType -> WebStorageType
Ord, WebStorageType
WebStorageType -> WebStorageType -> Bounded WebStorageType
forall a. a -> a -> Bounded a
$cminBound :: WebStorageType
minBound :: WebStorageType
$cmaxBound :: WebStorageType
maxBound :: WebStorageType
Bounded, Int -> WebStorageType
WebStorageType -> Int
WebStorageType -> [WebStorageType]
WebStorageType -> WebStorageType
WebStorageType -> WebStorageType -> [WebStorageType]
WebStorageType
-> WebStorageType -> WebStorageType -> [WebStorageType]
(WebStorageType -> WebStorageType)
-> (WebStorageType -> WebStorageType)
-> (Int -> WebStorageType)
-> (WebStorageType -> Int)
-> (WebStorageType -> [WebStorageType])
-> (WebStorageType -> WebStorageType -> [WebStorageType])
-> (WebStorageType -> WebStorageType -> [WebStorageType])
-> (WebStorageType
-> WebStorageType -> WebStorageType -> [WebStorageType])
-> Enum WebStorageType
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 :: WebStorageType -> WebStorageType
succ :: WebStorageType -> WebStorageType
$cpred :: WebStorageType -> WebStorageType
pred :: WebStorageType -> WebStorageType
$ctoEnum :: Int -> WebStorageType
toEnum :: Int -> WebStorageType
$cfromEnum :: WebStorageType -> Int
fromEnum :: WebStorageType -> Int
$cenumFrom :: WebStorageType -> [WebStorageType]
enumFrom :: WebStorageType -> [WebStorageType]
$cenumFromThen :: WebStorageType -> WebStorageType -> [WebStorageType]
enumFromThen :: WebStorageType -> WebStorageType -> [WebStorageType]
$cenumFromTo :: WebStorageType -> WebStorageType -> [WebStorageType]
enumFromTo :: WebStorageType -> WebStorageType -> [WebStorageType]
$cenumFromThenTo :: WebStorageType
-> WebStorageType -> WebStorageType -> [WebStorageType]
enumFromThenTo :: WebStorageType
-> WebStorageType -> WebStorageType -> [WebStorageType]
Enum)
getKey :: (HasCallStack, WebDriver wd) => WebStorageType -> Text -> wd Text
getKey :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> Text -> wd Text
getKey WebStorageType
s Text
k = Method -> WebStorageType -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodGet WebStorageType
s (Text
"/key/" Text -> Text -> Text
`T.append` Text -> Text
urlEncode Text
k) Value
Null
setKey :: (HasCallStack, WebDriver wd) => WebStorageType -> Text -> Text -> wd Text
setKey :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> Text -> Text -> wd Text
setKey WebStorageType
s Text
k Text
v = Method -> WebStorageType -> Text -> Value -> wd Text
forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodPost WebStorageType
s Text
"" (Value -> wd Text) -> ([Pair] -> Value) -> [Pair] -> wd Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
object ([Pair] -> wd Text) -> [Pair] -> wd Text
forall a b. (a -> b) -> a -> b
$ [Key
"key" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
k,
Key
"value" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
v ]
deleteKey :: (HasCallStack, WebDriver wd) => WebStorageType -> Text -> wd ()
deleteKey :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> Text -> wd ()
deleteKey WebStorageType
s Text
k = wd NoReturn -> wd ()
forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> WebStorageType -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodPost WebStorageType
s (Text
"/key/" Text -> Text -> Text
`T.append` Text -> Text
urlEncode Text
k) Value
Null
doStorageCommand :: (WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand :: forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
m WebStorageType
s Text
path a
a = Method -> Text -> a -> wd b
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
m ([Text] -> Text
T.concat [Text
"/", Text
s', Text
path]) a
a
where s' :: Text
s' = case WebStorageType
s of
WebStorageType
LocalStorage -> Text
"local_storage"
WebStorageType
SessionStorage -> Text
"session_storage"
serverStatus :: (WebDriver wd) => wd Value
serverStatus :: forall (wd :: * -> *). WebDriver wd => wd Value
serverStatus = Method -> Text -> Value -> wd Value
forall a b.
(HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
forall (wd :: * -> *) a b.
(WebDriver wd, HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doCommand Method
methodGet Text
"/status" Value
Null
data LogEntry =
LogEntry { LogEntry -> Integer
logTime :: Integer
, LogEntry -> LogLevel
logLevel :: LogLevel
, LogEntry -> Text
logMsg :: Text
}
deriving (LogEntry -> LogEntry -> Bool
(LogEntry -> LogEntry -> Bool)
-> (LogEntry -> LogEntry -> Bool) -> Eq LogEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogEntry -> LogEntry -> Bool
== :: LogEntry -> LogEntry -> Bool
$c/= :: LogEntry -> LogEntry -> Bool
/= :: LogEntry -> LogEntry -> Bool
Eq, Eq LogEntry
Eq LogEntry =>
(LogEntry -> LogEntry -> Ordering)
-> (LogEntry -> LogEntry -> Bool)
-> (LogEntry -> LogEntry -> Bool)
-> (LogEntry -> LogEntry -> Bool)
-> (LogEntry -> LogEntry -> Bool)
-> (LogEntry -> LogEntry -> LogEntry)
-> (LogEntry -> LogEntry -> LogEntry)
-> Ord LogEntry
LogEntry -> LogEntry -> Bool
LogEntry -> LogEntry -> Ordering
LogEntry -> LogEntry -> LogEntry
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 :: LogEntry -> LogEntry -> Ordering
compare :: LogEntry -> LogEntry -> Ordering
$c< :: LogEntry -> LogEntry -> Bool
< :: LogEntry -> LogEntry -> Bool
$c<= :: LogEntry -> LogEntry -> Bool
<= :: LogEntry -> LogEntry -> Bool
$c> :: LogEntry -> LogEntry -> Bool
> :: LogEntry -> LogEntry -> Bool
$c>= :: LogEntry -> LogEntry -> Bool
>= :: LogEntry -> LogEntry -> Bool
$cmax :: LogEntry -> LogEntry -> LogEntry
max :: LogEntry -> LogEntry -> LogEntry
$cmin :: LogEntry -> LogEntry -> LogEntry
min :: LogEntry -> LogEntry -> LogEntry
Ord, Int -> LogEntry -> ShowS
[LogEntry] -> ShowS
LogEntry -> String
(Int -> LogEntry -> ShowS)
-> (LogEntry -> String) -> ([LogEntry] -> ShowS) -> Show LogEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogEntry -> ShowS
showsPrec :: Int -> LogEntry -> ShowS
$cshow :: LogEntry -> String
show :: LogEntry -> String
$cshowList :: [LogEntry] -> ShowS
showList :: [LogEntry] -> ShowS
Show, ReadPrec [LogEntry]
ReadPrec LogEntry
Int -> ReadS LogEntry
ReadS [LogEntry]
(Int -> ReadS LogEntry)
-> ReadS [LogEntry]
-> ReadPrec LogEntry
-> ReadPrec [LogEntry]
-> Read LogEntry
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LogEntry
readsPrec :: Int -> ReadS LogEntry
$creadList :: ReadS [LogEntry]
readList :: ReadS [LogEntry]
$creadPrec :: ReadPrec LogEntry
readPrec :: ReadPrec LogEntry
$creadListPrec :: ReadPrec [LogEntry]
readListPrec :: ReadPrec [LogEntry]
Read)
instance FromJSON LogEntry where
parseJSON :: Value -> Parser LogEntry
parseJSON (Object Object
o) =
Integer -> LogLevel -> Text -> LogEntry
LogEntry (Integer -> LogLevel -> Text -> LogEntry)
-> Parser Integer -> Parser (LogLevel -> Text -> LogEntry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timestamp"
Parser (LogLevel -> Text -> LogEntry)
-> Parser LogLevel -> Parser (Text -> LogEntry)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser LogLevel
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"level"
Parser (Text -> LogEntry) -> Parser Text -> Parser LogEntry
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Parser (Maybe Text) -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"message")
parseJSON Value
v = String -> Value -> Parser LogEntry
forall a. String -> Value -> Parser a
typeMismatch String
"LogEntry" Value
v
type LogType = String
getLogs :: (HasCallStack, WebDriver wd) => LogType -> wd [LogEntry]
getLogs :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd [LogEntry]
getLogs String
t = Method -> Text -> Value -> wd [LogEntry]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/log" (Value -> wd [LogEntry])
-> ([Pair] -> Value) -> [Pair] -> wd [LogEntry]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
object ([Pair] -> wd [LogEntry]) -> [Pair] -> wd [LogEntry]
forall a b. (a -> b) -> a -> b
$ [Key
"type" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= String
t]
getLogTypes :: (HasCallStack, WebDriver wd) => wd [LogType]
getLogTypes :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [String]
getLogTypes = Method -> Text -> Value -> wd [String]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/log/types" Value
Null
data ApplicationCacheStatus = Uncached | Idle | Checking | Downloading | UpdateReady | Obsolete deriving (ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
(ApplicationCacheStatus -> ApplicationCacheStatus -> Bool)
-> (ApplicationCacheStatus -> ApplicationCacheStatus -> Bool)
-> Eq ApplicationCacheStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
== :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$c/= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
/= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
Eq, Int -> ApplicationCacheStatus
ApplicationCacheStatus -> Int
ApplicationCacheStatus -> [ApplicationCacheStatus]
ApplicationCacheStatus -> ApplicationCacheStatus
ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [ApplicationCacheStatus]
(ApplicationCacheStatus -> ApplicationCacheStatus)
-> (ApplicationCacheStatus -> ApplicationCacheStatus)
-> (Int -> ApplicationCacheStatus)
-> (ApplicationCacheStatus -> Int)
-> (ApplicationCacheStatus -> [ApplicationCacheStatus])
-> (ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus])
-> (ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus])
-> (ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [ApplicationCacheStatus])
-> Enum ApplicationCacheStatus
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 :: ApplicationCacheStatus -> ApplicationCacheStatus
succ :: ApplicationCacheStatus -> ApplicationCacheStatus
$cpred :: ApplicationCacheStatus -> ApplicationCacheStatus
pred :: ApplicationCacheStatus -> ApplicationCacheStatus
$ctoEnum :: Int -> ApplicationCacheStatus
toEnum :: Int -> ApplicationCacheStatus
$cfromEnum :: ApplicationCacheStatus -> Int
fromEnum :: ApplicationCacheStatus -> Int
$cenumFrom :: ApplicationCacheStatus -> [ApplicationCacheStatus]
enumFrom :: ApplicationCacheStatus -> [ApplicationCacheStatus]
$cenumFromThen :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
enumFromThen :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
$cenumFromTo :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
enumFromTo :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
$cenumFromThenTo :: ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [ApplicationCacheStatus]
enumFromThenTo :: ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [ApplicationCacheStatus]
Enum, ApplicationCacheStatus
ApplicationCacheStatus
-> ApplicationCacheStatus -> Bounded ApplicationCacheStatus
forall a. a -> a -> Bounded a
$cminBound :: ApplicationCacheStatus
minBound :: ApplicationCacheStatus
$cmaxBound :: ApplicationCacheStatus
maxBound :: ApplicationCacheStatus
Bounded, Eq ApplicationCacheStatus
Eq ApplicationCacheStatus =>
(ApplicationCacheStatus -> ApplicationCacheStatus -> Ordering)
-> (ApplicationCacheStatus -> ApplicationCacheStatus -> Bool)
-> (ApplicationCacheStatus -> ApplicationCacheStatus -> Bool)
-> (ApplicationCacheStatus -> ApplicationCacheStatus -> Bool)
-> (ApplicationCacheStatus -> ApplicationCacheStatus -> Bool)
-> (ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus)
-> (ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus)
-> Ord ApplicationCacheStatus
ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
ApplicationCacheStatus -> ApplicationCacheStatus -> Ordering
ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
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 :: ApplicationCacheStatus -> ApplicationCacheStatus -> Ordering
compare :: ApplicationCacheStatus -> ApplicationCacheStatus -> Ordering
$c< :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
< :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$c<= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
<= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$c> :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
> :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$c>= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
>= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$cmax :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
max :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
$cmin :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
min :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
Ord, Int -> ApplicationCacheStatus -> ShowS
[ApplicationCacheStatus] -> ShowS
ApplicationCacheStatus -> String
(Int -> ApplicationCacheStatus -> ShowS)
-> (ApplicationCacheStatus -> String)
-> ([ApplicationCacheStatus] -> ShowS)
-> Show ApplicationCacheStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationCacheStatus -> ShowS
showsPrec :: Int -> ApplicationCacheStatus -> ShowS
$cshow :: ApplicationCacheStatus -> String
show :: ApplicationCacheStatus -> String
$cshowList :: [ApplicationCacheStatus] -> ShowS
showList :: [ApplicationCacheStatus] -> ShowS
Show, ReadPrec [ApplicationCacheStatus]
ReadPrec ApplicationCacheStatus
Int -> ReadS ApplicationCacheStatus
ReadS [ApplicationCacheStatus]
(Int -> ReadS ApplicationCacheStatus)
-> ReadS [ApplicationCacheStatus]
-> ReadPrec ApplicationCacheStatus
-> ReadPrec [ApplicationCacheStatus]
-> Read ApplicationCacheStatus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ApplicationCacheStatus
readsPrec :: Int -> ReadS ApplicationCacheStatus
$creadList :: ReadS [ApplicationCacheStatus]
readList :: ReadS [ApplicationCacheStatus]
$creadPrec :: ReadPrec ApplicationCacheStatus
readPrec :: ReadPrec ApplicationCacheStatus
$creadListPrec :: ReadPrec [ApplicationCacheStatus]
readListPrec :: ReadPrec [ApplicationCacheStatus]
Read)
instance FromJSON ApplicationCacheStatus where
parseJSON :: Value -> Parser ApplicationCacheStatus
parseJSON Value
val = do
Integer
n <- Value -> Parser Integer
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
case Integer
n :: Integer of
Integer
0 -> ApplicationCacheStatus -> Parser ApplicationCacheStatus
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Uncached
Integer
1 -> ApplicationCacheStatus -> Parser ApplicationCacheStatus
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Idle
Integer
2 -> ApplicationCacheStatus -> Parser ApplicationCacheStatus
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Checking
Integer
3 -> ApplicationCacheStatus -> Parser ApplicationCacheStatus
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Downloading
Integer
4 -> ApplicationCacheStatus -> Parser ApplicationCacheStatus
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
UpdateReady
Integer
5 -> ApplicationCacheStatus -> Parser ApplicationCacheStatus
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Obsolete
Integer
err -> String -> Parser ApplicationCacheStatus
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ApplicationCacheStatus)
-> String -> Parser ApplicationCacheStatus
forall a b. (a -> b) -> a -> b
$ String
"Invalid JSON for ApplicationCacheStatus: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
err
getApplicationCacheStatus :: (WebDriver wd) => wd ApplicationCacheStatus
getApplicationCacheStatus :: forall (wd :: * -> *). WebDriver wd => wd ApplicationCacheStatus
getApplicationCacheStatus = Method -> Text -> Value -> wd ApplicationCacheStatus
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/application_cache/status" Value
Null