{-# LANGUAGE ExistentialQuantification #-}

-- | This module exports basic WD actions that can be used to interact with a
-- browser session.
module Test.WebDriver.Commands
       ( -- * Sessions
         createSession, closeSession, sessions, getActualCaps
         -- * Browser interaction
         -- ** Web navigation
       , openPage, forward, back, refresh
         -- ** Page info
       , getCurrentURL, getSource, getTitle, saveScreenshot, screenshot, screenshotBase64
         -- * Timeouts
       , setImplicitWait, setScriptTimeout, setPageLoadTimeout
         -- * Web elements
       , Element(..), Selector(..)
         -- ** Searching for elements
       , findElem, findElems, findElemFrom, findElemsFrom
         -- ** Interacting with elements
       , click, submit, getText
         -- *** Sending key inputs to elements
       , sendKeys, sendRawKeys, clearInput
         -- ** Element information
       , attr, cssProp, elemPos, elemSize
       , isSelected, isEnabled, isDisplayed
       , tagName, activeElem, elemInfo
         -- ** Element equality
       , (<==>), (</=>)
         -- * Javascript
       , executeJS, asyncJS
       , JSArg(..)
         -- * Windows
       , WindowHandle(..), currentWindow
       , getCurrentWindow, closeWindow, windows, focusWindow,  maximize
       , getWindowSize, setWindowSize, getWindowPos, setWindowPos
         -- * Focusing on frames
       , focusFrame, FrameSelector(..)
         -- * Cookies
       , Cookie(..), mkCookie
       , cookies, setCookie, deleteCookie, deleteVisibleCookies, deleteCookieByName
         -- * Alerts
       , getAlertText, replyToAlert, acceptAlert, dismissAlert
         -- * Mouse gestures
       , moveTo, moveToCenter, moveToFrom
       , clickWith, MouseButton(..)
       , mouseDown, mouseUp, withMouseDown, doubleClick
         -- * HTML 5 Web Storage
       , WebStorageType(..), storageSize, getAllKeys, deleteAllKeys
       , getKey, setKey, deleteKey
         -- * HTML 5 Application Cache
       , ApplicationCacheStatus(..)
       , getApplicationCacheStatus
         -- * Mobile device support
         -- ** Screen orientation
       , Orientation(..)
       , getOrientation, setOrientation
         -- ** Geo-location
       , getLocation, setLocation
         -- ** Touch gestures
       , touchClick, touchDown, touchUp, touchMove
       , touchScroll, touchScrollFrom, touchDoubleClick
       , touchLongClick, touchFlick, touchFlickFrom
         -- * IME support
       , availableIMEEngines, activeIMEEngine, checkIMEActive
       , activateIME, deactivateIME
         -- * Uploading files to remote server
         -- |These functions allow you to upload a file to a remote server.
         -- Note that this operation isn't supported by all WebDriver servers,
         -- and the location where the file is stored is not standardized.
       , uploadFile, uploadRawFile, uploadZipEntry
         -- * Server information and logs
       , 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)  -- suppresses warnings
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 -- hides some "unused import" warnings

-- |Create a new session with the given 'Capabilities'. The returned session becomes the \"current session\" for this action.
--
-- Note: if you're using 'runSession' to run your WebDriver commands, you don't need to call this explicitly.
createSession :: (HasCallStack, WebDriver wd) => Capabilities -> wd WDSession
createSession :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Capabilities -> wd WDSession
createSession Capabilities
caps = do
  forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. WDSessionStateControl m => m a -> m a
withAuthHeaders forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(WebDriver wd, HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doCommand Method
methodPost Text
"/session" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"desiredCapabilities" forall a b. (a -> b) -> a -> b
$ Capabilities
caps
  forall (m :: * -> *). WDSessionState m => m WDSession
getSession

-- |Retrieve a list of active sessions and their 'Capabilities'.
sessions :: (HasCallStack, WebDriver wd) => wd [(SessionId, Capabilities)]
sessions :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd [(SessionId, Capabilities)]
sessions = do
  [Value]
objs <- forall (wd :: * -> *) a b.
(WebDriver wd, HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doCommand Method
methodGet Text
"/sessions" Value
Null
  forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (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

-- |Get the actual server-side 'Capabilities' of the current session.
getActualCaps :: (HasCallStack, WebDriver wd) => wd Capabilities
getActualCaps :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd Capabilities
getActualCaps = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"" Value
Null

-- |Close the current session and the browser associated with it.
closeSession :: (HasCallStack, WebDriver wd) => wd ()
closeSession :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
closeSession = do s :: WDSession
s@WDSession {} <- forall (m :: * -> *). WDSessionState m => m WDSession
getSession
                  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"" Value
Null
                  forall (m :: * -> *). WDSessionState m => WDSession -> m ()
putSession WDSession
s { wdSessId :: Maybe SessionId
wdSessId = forall a. Maybe a
Nothing }


-- |Sets the amount of time (ms) we implicitly wait when searching for elements.
setImplicitWait :: (HasCallStack, WebDriver wd) => Integer -> wd ()
setImplicitWait :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Integer -> wd ()
setImplicitWait Integer
ms =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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)
    forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> (e -> m a) -> m a
`L.catch` \(SomeException
_ :: SomeException) ->
      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" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Integer
ms]
        allFields :: [Pair]
allFields = [Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (String
"implicit" :: String)] forall a. [a] -> [a] -> [a]
++ [Pair]
msField

-- |Sets the amount of time (ms) we wait for an asynchronous script to return a
-- result.
setScriptTimeout :: (HasCallStack, WebDriver wd) => Integer -> wd ()
setScriptTimeout :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Integer -> wd ()
setScriptTimeout Integer
ms =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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)
    forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> (e -> m a) -> m a
`L.catch` \( SomeException
_ :: SomeException) ->
      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" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Integer
ms]
        allFields :: [Pair]
allFields = [Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (String
"script" :: String)] forall a. [a] -> [a] -> [a]
++ [Pair]
msField

-- |Sets the amount of time (ms) to wait for a page to finish loading before throwing a 'Timeout' exception.
setPageLoadTimeout :: (HasCallStack, WebDriver wd) => Integer -> wd ()
setPageLoadTimeout :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Integer -> wd ()
setPageLoadTimeout Integer
ms = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (String
"page load" :: String)
                        ,Key
"ms"   forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Integer
ms ]

-- |Gets the URL of the current page.
getCurrentURL :: (HasCallStack, WebDriver wd) => wd String
getCurrentURL :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd String
getCurrentURL = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/url" Value
Null

-- |Opens a new page by the given URL.
openPage :: (HasCallStack, WebDriver wd) => String -> wd ()
openPage :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd ()
openPage String
url
  | String -> Bool
isURI String
url = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/url" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"url" forall a b. (a -> b) -> a -> b
$ String
url
  | Bool
otherwise = forall (m :: * -> *) e a. (MonadBase IO m, Exception e) => e -> m a
throwIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> InvalidURL
InvalidURL forall a b. (a -> b) -> a -> b
$ String
url

-- |Navigate forward in the browser history.
forward :: (HasCallStack, WebDriver wd) => wd ()
forward :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
forward = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/forward" Value
Null

-- |Navigate backward in the browser history.
back :: (HasCallStack, WebDriver wd) => wd ()
back :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
back = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/back" Value
Null

-- |Refresh the current page
refresh :: (HasCallStack, WebDriver wd) => wd ()
refresh :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
refresh = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/refresh" Value
Null

-- |An existential wrapper for any 'ToJSON' instance. This allows us to pass
-- parameters of many different types to Javascript code.
data JSArg = forall a. ToJSON a => JSArg a

instance ToJSON JSArg where
  toJSON :: JSArg -> Value
toJSON (JSArg a
a) = forall a. ToJSON a => a -> Value
toJSON a
a

{- |Inject a snippet of Javascript into the page for execution in the
context of the currently selected frame. The executed script is
assumed to be synchronous and the result of evaluating the script is
returned and converted to an instance of FromJSON.

The first parameter defines a sequence of arguments to pass to the javascript
function. Arguments of type Element will be converted to the
corresponding DOM element. Likewise, any elements in the script result
will be returned to the client as Elements.

The second parameter defines the script itself in the form of a
function body. The value returned by that function will be returned to
the client. The function will be invoked with the provided argument
list and the values may be accessed via the arguments object in the
order specified.

When using 'executeJS', GHC might complain about an ambiguous type in
situations where the result of the executeJS call is ignored/discard.
Consider the following example:

@
	jsExample = do
		e <- findElem (ById "foo")
		executeJS [] "someAction()"
		return e
@

Because the result of the 'executeJS' is discarded, GHC cannot resolve
which instance of the 'fromJSON' class to use when parsing the
Selenium server response. In such cases, we can use the 'ignoreReturn'
helper function located in "Test.WebDriver.JSON". 'ignoreReturn' has
no runtime effect; it simply helps the type system by expicitly providing
a `fromJSON` instance to use.

@
	import Test.WebDriver.JSON (ignoreReturn)
	jsExample = do
		e <- findElem (ById "foo")
		ignoreReturn $ executeJS [] "someAction()"
		return e
@
-}
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 = forall (wd :: * -> *) a.
(MonadBaseControl IO wd, FromJSON a) =>
Value -> wd a
fromJSON' forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< wd Value
getResult
  where
    getResult :: wd Value
getResult = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/execute" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"args", Text
"script") forall a b. (a -> b) -> a -> b
$ (forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList f JSArg
a,Text
s)

{- |Executes a snippet of Javascript code asynchronously. This function works
similarly to 'executeJS', except that the Javascript is passed a callback
function as its final argument. The script should call this function
to signal that it has finished executing, passing to it a value that will be
returned as the result of asyncJS. A result of Nothing indicates that the
Javascript function timed out (see 'setScriptTimeout')
-}
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 = forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
(e -> m a) -> m a -> m a
handle forall {m :: * -> *} {a}.
MonadBase IO m =>
FailedCommand -> m (Maybe a)
timeout forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (wd :: * -> *) a.
(MonadBaseControl IO wd, FromJSON a) =>
Value -> wd a
fromJSON' forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< wd Value
getResult)
  where
    getResult :: wd Value
getResult = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/execute_async" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"args", Text
"script")
                forall a b. (a -> b) -> a -> b
$ (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
_)       = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    timeout (FailedCommand FailedCommandType
ScriptTimeout FailedCommandInfo
_) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    timeout FailedCommand
err = forall (m :: * -> *) e a. (MonadBase IO m, Exception e) => e -> m a
throwIO FailedCommand
err

-- |Save a screenshot to a particular location
saveScreenshot :: (HasCallStack, WebDriver wd) => FilePath -> wd ()
saveScreenshot :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd ()
saveScreenshot String
path = forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshot forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString -> IO ()
LBS.writeFile String
path

-- |Grab a screenshot of the current page as a PNG image
screenshot :: (HasCallStack, WebDriver wd) => wd LBS.ByteString
screenshot :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshot = ByteString -> ByteString
B64.decodeLenient forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshotBase64

-- |Grab a screenshot as a base-64 encoded PNG image. This is the protocol-defined format.
screenshotBase64 :: (HasCallStack, WebDriver wd) => wd LBS.ByteString
screenshotBase64 :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd ByteString
screenshotBase64 = Text -> ByteString
TL.encodeUtf8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 = 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 = 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 = 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 = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/ime/activate" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"engine"

deactivateIME :: (HasCallStack, WebDriver wd) => wd ()
deactivateIME :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
deactivateIME = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/ime/deactivate" Value
Null


-- |Specifies the frame used by 'Test.WebDriver.Commands.focusFrame'
data FrameSelector = WithIndex Integer
                     -- |focus on a frame by name or ID
                   | WithName Text
                     -- |focus on a frame 'Element'
                   | WithElement Element
                     -- |focus on the first frame, or the main document
                     -- if iframes are used.
                   | DefaultFrame
                   deriving (FrameSelector -> FrameSelector -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameSelector -> FrameSelector -> Bool
$c/= :: FrameSelector -> FrameSelector -> Bool
== :: FrameSelector -> FrameSelector -> Bool
$c== :: FrameSelector -> FrameSelector -> Bool
Eq, Int -> FrameSelector -> ShowS
[FrameSelector] -> ShowS
FrameSelector -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameSelector] -> ShowS
$cshowList :: [FrameSelector] -> ShowS
show :: FrameSelector -> String
$cshow :: FrameSelector -> String
showsPrec :: Int -> FrameSelector -> ShowS
$cshowsPrec :: Int -> FrameSelector -> ShowS
Show, ReadPrec [FrameSelector]
ReadPrec FrameSelector
Int -> ReadS FrameSelector
ReadS [FrameSelector]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FrameSelector]
$creadListPrec :: ReadPrec [FrameSelector]
readPrec :: ReadPrec FrameSelector
$creadPrec :: ReadPrec FrameSelector
readList :: ReadS [FrameSelector]
$creadList :: ReadS [FrameSelector]
readsPrec :: Int -> ReadS FrameSelector
$creadsPrec :: Int -> ReadS FrameSelector
Read)

instance ToJSON FrameSelector where
  toJSON :: FrameSelector -> Value
toJSON FrameSelector
s = case FrameSelector
s of
    WithIndex Integer
i -> forall a. ToJSON a => a -> Value
toJSON Integer
i
    WithName Text
n -> forall a. ToJSON a => a -> Value
toJSON Text
n
    WithElement Element
e -> forall a. ToJSON a => a -> Value
toJSON Element
e
    FrameSelector
DefaultFrame -> Value
Null

-- |Switch focus to the frame specified by the FrameSelector.
focusFrame :: (HasCallStack, WebDriver wd) => FrameSelector -> wd ()
focusFrame :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
FrameSelector -> wd ()
focusFrame FrameSelector
s = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/frame" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"id" forall a b. (a -> b) -> a -> b
$ FrameSelector
s

-- |Returns a handle to the currently focused window
getCurrentWindow :: (HasCallStack, WebDriver wd) => wd WindowHandle
getCurrentWindow :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd WindowHandle
getCurrentWindow = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/window_handle" Value
Null

-- |Returns a list of all windows available to the session
windows :: (HasCallStack, WebDriver wd) => wd [WindowHandle]
windows :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd [WindowHandle]
windows = 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 = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/window" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"handle" forall a b. (a -> b) -> a -> b
$ WindowHandle
w

-- |Closes the given window
closeWindow :: (HasCallStack, WebDriver wd) => WindowHandle -> wd ()
closeWindow :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
closeWindow WindowHandle
w = do
  WindowHandle
cw <- forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd WindowHandle
getCurrentWindow
  forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
focusWindow WindowHandle
w
  forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"/window" Value
Null
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (WindowHandle
w forall a. Eq a => a -> a -> Bool
== WindowHandle
cw) forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WindowHandle -> wd ()
focusWindow WindowHandle
cw

-- |Maximizes the current  window if not already maximized
maximize :: (HasCallStack, WebDriver wd) => wd ()
maximize :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
maximize = forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn forall a b. (a -> b) -> a -> b
$ 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

-- |Get the dimensions of the current window.
getWindowSize :: (HasCallStack, WebDriver wd) => wd (Word, Word)
getWindowSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd (Word, Word)
getWindowSize = 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
                forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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"

-- |Set the dimensions of the current window.
setWindowSize :: (HasCallStack, WebDriver wd) => (Word, Word) -> wd ()
setWindowSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Word, Word) -> wd ()
setWindowSize = forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodPost WindowHandle
currentWindow Text
"/size"
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"width", Text
"height")

-- |Get the coordinates of the current window.
getWindowPos :: (HasCallStack, WebDriver wd) => wd (Int, Int)
getWindowPos :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd (Int, Int)
getWindowPos = 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
               forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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"

-- |Set the coordinates of the current window.
setWindowPos :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
setWindowPos :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
setWindowPos = forall (wd :: * -> *). WebDriver wd => wd Value -> wd ()
ignoreReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WindowHandle -> Text -> a -> wd b
doWinCommand Method
methodPost WindowHandle
currentWindow Text
"/position" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")

-- |Retrieve all cookies visible to the current page.
cookies :: (HasCallStack, WebDriver wd) => wd [Cookie]
cookies :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [Cookie]
cookies = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/cookie" Value
Null

-- |Set a cookie. If the cookie path is not specified, it will default to \"/\".
-- Likewise, if the domain is omitted, it will default to the current page's
-- domain
setCookie :: (HasCallStack, WebDriver wd) => Cookie -> wd ()
setCookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Cookie -> wd ()
setCookie = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/cookie" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"cookie"

-- |Delete a cookie. This will do nothing is the cookie isn't visible to the
-- current page.
deleteCookie :: (HasCallStack, WebDriver wd) => Cookie -> wd ()
deleteCookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Cookie -> wd ()
deleteCookie Cookie
c = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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 = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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

-- |Delete all visible cookies on the current page.
deleteVisibleCookies :: (HasCallStack, WebDriver wd) => wd ()
deleteVisibleCookies :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
deleteVisibleCookies = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"/cookie" Value
Null

-- |Get the current page source
getSource :: (HasCallStack, WebDriver wd) => wd Text
getSource :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
getSource = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/source" Value
Null

-- |Get the title of the current page.
getTitle :: (HasCallStack, WebDriver wd) => wd Text
getTitle :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
getTitle = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/title" Value
Null

-- |Specifies element(s) within a DOM tree using various selection methods.
data Selector = ById Text
              | ByName Text
              | ByClass Text -- ^ (Note: multiple classes are not
                             -- allowed. For more control, use 'ByCSS')
              | ByTag Text
              | ByLinkText Text
              | ByPartialLinkText Text
              | ByCSS Text
              | ByXPath Text
              deriving (Selector -> Selector -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Selector -> Selector -> Bool
$c/= :: Selector -> Selector -> Bool
== :: Selector -> Selector -> Bool
$c== :: Selector -> Selector -> Bool
Eq, Int -> Selector -> ShowS
[Selector] -> ShowS
Selector -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Selector] -> ShowS
$cshowList :: [Selector] -> ShowS
show :: Selector -> String
$cshow :: Selector -> String
showsPrec :: Int -> Selector -> ShowS
$cshowsPrec :: Int -> Selector -> ShowS
Show, Eq 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
min :: Selector -> Selector -> Selector
$cmin :: Selector -> Selector -> Selector
max :: Selector -> Selector -> Selector
$cmax :: Selector -> Selector -> Selector
>= :: Selector -> Selector -> Bool
$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
compare :: Selector -> Selector -> Ordering
$ccompare :: Selector -> Selector -> Ordering
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" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
sn, Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
t]

-- |Find an element on the page using the given element selector.
findElem :: (HasCallStack, WebDriver wd) => Selector -> wd Element
findElem :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Selector -> wd Element
findElem = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/element"

-- |Find all elements on the page matching the given selector.
findElems :: (HasCallStack, WebDriver wd) => Selector -> wd [Element]
findElems :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Selector -> wd [Element]
findElems = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/elements"

-- |Return the element that currently has focus.
activeElem :: (HasCallStack, WebDriver wd) => wd Element
activeElem :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Element
activeElem = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/element/active" Value
Null

-- |Search for an element using the given element as root.
findElemFrom :: (HasCallStack, WebDriver wd) => Element -> Selector -> wd Element
findElemFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Selector -> wd Element
findElemFrom Element
e = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/element"

-- |Find all elements matching a selector, using the given element as root.
findElemsFrom :: (HasCallStack, WebDriver wd) => Element -> Selector -> wd [Element]
findElemsFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Selector -> wd [Element]
findElemsFrom Element
e = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/elements"

-- |Describe the element. Returns a JSON object whose meaning is currently
-- undefined by the WebDriver protocol.
elemInfo :: (HasCallStack, WebDriver wd) => Element -> wd Value
elemInfo :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Value
elemInfo Element
e = 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 on an element.
click :: (HasCallStack, WebDriver wd) => Element -> wd ()
click :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
click Element
e = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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 a form element. This may be applied to descendents of a form element
-- as well.
submit :: (HasCallStack, WebDriver wd) => Element -> wd ()
submit :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
submit Element
e = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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

-- |Get all visible text within this element.
getText :: (HasCallStack, WebDriver wd) => Element -> wd Text
getText :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Text
getText Element
e = 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

-- |Send a sequence of keystrokes to an element. All modifier keys are released
-- at the end of the function. Named constants for special modifier keys can be found
-- in "Test.WebDriver.Common.Keys"
sendKeys :: (HasCallStack, WebDriver wd) => Text -> Element -> wd ()
sendKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> Element -> wd ()
sendKeys Text
t Element
e = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Element -> Text -> a -> wd b
doElemCommand Method
methodPost Element
e Text
"/value" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"value" forall a b. (a -> b) -> a -> b
$ [Text
t]

-- |Similar to sendKeys, but doesn't implicitly release modifier keys
-- afterwards. This allows you to combine modifiers with mouse clicks.
sendRawKeys :: (HasCallStack, WebDriver wd) => Text -> wd ()
sendRawKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
sendRawKeys Text
t = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/keys" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"value" forall a b. (a -> b) -> a -> b
$ [Text
t]

-- |Return the tag name of the given element.
tagName :: (HasCallStack, WebDriver wd) => Element -> wd Text
tagName :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Text
tagName Element
e = 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

-- |Clear a textarea or text input element's value.
clearInput :: (HasCallStack, WebDriver wd) => Element -> wd ()
clearInput :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
clearInput Element
e = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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

-- |Determine if the element is selected.
isSelected :: (HasCallStack, WebDriver wd) => Element -> wd Bool
isSelected :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Bool
isSelected Element
e = 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

-- |Determine if the element is enabled.
isEnabled :: (HasCallStack, WebDriver wd) => Element -> wd Bool
isEnabled :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Bool
isEnabled Element
e = 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

-- |Determine if the element is displayed.
isDisplayed :: (HasCallStack, WebDriver wd) => Element -> wd Bool
isDisplayed :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Bool
isDisplayed Element
e = 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

-- |Retrieve the value of an element's attribute
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 = 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

-- |Retrieve the value of an element's computed CSS property
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 = 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

-- |Retrieve an element's current position.
elemPos :: (HasCallStack, WebDriver wd) => Element -> wd (Float, Float)
elemPos :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd (Float, Float)
elemPos Element
e = 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 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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"

-- |Retrieve an element's current size.
elemSize :: (HasCallStack, WebDriver wd) => Element -> wd (Float, Float)
elemSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd (Float, Float)
elemSize Element
e = 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
             forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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 <==>
-- |Determines if two element identifiers refer to the same element.
(<==>) :: (HasCallStack, WebDriver wd) => Element -> Element -> wd Bool
Element
e1 <==> :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Element -> wd Bool
<==> (Element Text
e2) = 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

-- |Determines if two element identifiers refer to different elements.
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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Element
e1 forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Element -> wd Bool
<==> Element
e2)

-- |A screen orientation
data Orientation = Landscape | Portrait
                 deriving (Orientation -> Orientation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Orientation -> Orientation -> Bool
$c/= :: Orientation -> Orientation -> Bool
== :: Orientation -> Orientation -> Bool
$c== :: Orientation -> Orientation -> Bool
Eq, Int -> Orientation -> ShowS
[Orientation] -> ShowS
Orientation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Orientation] -> ShowS
$cshowList :: [Orientation] -> ShowS
show :: Orientation -> String
$cshow :: Orientation -> String
showsPrec :: Int -> Orientation -> ShowS
$cshowsPrec :: Int -> Orientation -> ShowS
Show, Eq 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
min :: Orientation -> Orientation -> Orientation
$cmin :: Orientation -> Orientation -> Orientation
max :: Orientation -> Orientation -> Orientation
$cmax :: Orientation -> Orientation -> Orientation
>= :: Orientation -> Orientation -> Bool
$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
compare :: Orientation -> Orientation -> Ordering
$ccompare :: Orientation -> Orientation -> Ordering
Ord, Orientation
forall a. a -> a -> Bounded a
maxBound :: Orientation
$cmaxBound :: Orientation
minBound :: Orientation
$cminBound :: Orientation
Bounded, Int -> Orientation
Orientation -> Int
Orientation -> [Orientation]
Orientation -> Orientation
Orientation -> Orientation -> [Orientation]
Orientation -> Orientation -> Orientation -> [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
enumFromThenTo :: Orientation -> Orientation -> Orientation -> [Orientation]
$cenumFromThenTo :: Orientation -> Orientation -> Orientation -> [Orientation]
enumFromTo :: Orientation -> Orientation -> [Orientation]
$cenumFromTo :: Orientation -> Orientation -> [Orientation]
enumFromThen :: Orientation -> Orientation -> [Orientation]
$cenumFromThen :: Orientation -> Orientation -> [Orientation]
enumFrom :: Orientation -> [Orientation]
$cenumFrom :: Orientation -> [Orientation]
fromEnum :: Orientation -> Int
$cfromEnum :: Orientation -> Int
toEnum :: Int -> Orientation
$ctoEnum :: Int -> Orientation
pred :: Orientation -> Orientation
$cpred :: Orientation -> Orientation
succ :: Orientation -> Orientation
$csucc :: Orientation -> Orientation
Enum)

instance ToJSON Orientation where
  toJSON :: Orientation -> Value
toJSON = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
toUpper forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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" -> forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
Landscape
    Text
"portrait"  -> forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
Portrait
    Text
err         -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Invalid Orientation string " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
err
  parseJSON Value
v = forall a. String -> Value -> Parser a
typeMismatch String
"Orientation" Value
v

-- |Get the current screen orientation for rotatable display devices.
getOrientation :: (HasCallStack, WebDriver wd) => wd Orientation
getOrientation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd Orientation
getOrientation = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/orientation" Value
Null

-- |Set the current screen orientation for rotatable display devices.
setOrientation :: (HasCallStack, WebDriver wd) => Orientation -> wd ()
setOrientation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Orientation -> wd ()
setOrientation = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/orientation" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"orientation"

-- |Get the text of an alert dialog.
getAlertText :: (HasCallStack, WebDriver wd) => wd Text
getAlertText :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd Text
getAlertText = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/alert_text" Value
Null

-- |Sends keystrokes to Javascript prompt() dialog.
replyToAlert :: (HasCallStack, WebDriver wd) => Text -> wd ()
replyToAlert :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
replyToAlert = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/alert_text" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"text"

-- |Accepts the currently displayed alert dialog.
acceptAlert :: (HasCallStack, WebDriver wd) => wd ()
acceptAlert :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
acceptAlert = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/accept_alert" Value
Null

-- |Dismisses the currently displayed alert dialog.
dismissAlert :: (HasCallStack, WebDriver wd) => wd ()
dismissAlert :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
dismissAlert = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/dismiss_alert" Value
Null

-- |Moves the mouse to the given position relative to the active element.
moveTo :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
moveTo :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
moveTo = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/moveto" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"xoffset",Text
"yoffset")

-- |Moves the mouse to the center of a given element.
moveToCenter :: (HasCallStack, WebDriver wd) => Element -> wd ()
moveToCenter :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
moveToCenter (Element Text
e) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/moveto" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"element" forall a b. (a -> b) -> a -> b
$ Text
e

-- |Moves the mouse to the given position relative to the given element.
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) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/moveto"
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c.
(ToJSON a, ToJSON b, ToJSON c) =>
(Text, Text, Text) -> (a, b, c) -> Value
triple (Text
"element",Text
"xoffset",Text
"yoffset") forall a b. (a -> b) -> a -> b
$ (Text
e,Int
x,Int
y)

-- |A mouse button
data MouseButton = LeftButton | MiddleButton | RightButton
                 deriving (MouseButton -> MouseButton -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MouseButton -> MouseButton -> Bool
$c/= :: MouseButton -> MouseButton -> Bool
== :: MouseButton -> MouseButton -> Bool
$c== :: MouseButton -> MouseButton -> Bool
Eq, Int -> MouseButton -> ShowS
[MouseButton] -> ShowS
MouseButton -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MouseButton] -> ShowS
$cshowList :: [MouseButton] -> ShowS
show :: MouseButton -> String
$cshow :: MouseButton -> String
showsPrec :: Int -> MouseButton -> ShowS
$cshowsPrec :: Int -> MouseButton -> ShowS
Show, Eq 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
min :: MouseButton -> MouseButton -> MouseButton
$cmin :: MouseButton -> MouseButton -> MouseButton
max :: MouseButton -> MouseButton -> MouseButton
$cmax :: MouseButton -> MouseButton -> MouseButton
>= :: MouseButton -> MouseButton -> Bool
$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
compare :: MouseButton -> MouseButton -> Ordering
$ccompare :: MouseButton -> MouseButton -> Ordering
Ord, MouseButton
forall a. a -> a -> Bounded a
maxBound :: MouseButton
$cmaxBound :: MouseButton
minBound :: MouseButton
$cminBound :: MouseButton
Bounded, Int -> MouseButton
MouseButton -> Int
MouseButton -> [MouseButton]
MouseButton -> MouseButton
MouseButton -> MouseButton -> [MouseButton]
MouseButton -> MouseButton -> MouseButton -> [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
enumFromThenTo :: MouseButton -> MouseButton -> MouseButton -> [MouseButton]
$cenumFromThenTo :: MouseButton -> MouseButton -> MouseButton -> [MouseButton]
enumFromTo :: MouseButton -> MouseButton -> [MouseButton]
$cenumFromTo :: MouseButton -> MouseButton -> [MouseButton]
enumFromThen :: MouseButton -> MouseButton -> [MouseButton]
$cenumFromThen :: MouseButton -> MouseButton -> [MouseButton]
enumFrom :: MouseButton -> [MouseButton]
$cenumFrom :: MouseButton -> [MouseButton]
fromEnum :: MouseButton -> Int
$cfromEnum :: MouseButton -> Int
toEnum :: Int -> MouseButton
$ctoEnum :: Int -> MouseButton
pred :: MouseButton -> MouseButton
$cpred :: MouseButton -> MouseButton
succ :: MouseButton -> MouseButton
$csucc :: MouseButton -> MouseButton
Enum)

instance ToJSON MouseButton where
  toJSON :: MouseButton -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum

instance FromJSON MouseButton where
  parseJSON :: Value -> Parser MouseButton
parseJSON Value
v = do
    Integer
n <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
    case Integer
n :: Integer of
      Integer
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return MouseButton
LeftButton
      Integer
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return MouseButton
MiddleButton
      Integer
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return MouseButton
RightButton
      Integer
err -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Invalid JSON for MouseButton: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
err

-- |Click at the current mouse position with the given mouse button.
clickWith :: (HasCallStack, WebDriver wd) => MouseButton -> wd ()
clickWith :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
MouseButton -> wd ()
clickWith = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/click" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"button"

-- |Perform the given action with the left mouse button held down. The mouse
-- is automatically released afterwards.
withMouseDown :: (HasCallStack, WebDriver wd) => wd a -> wd a
withMouseDown :: forall (wd :: * -> *) a.
(HasCallStack, WebDriver wd) =>
wd a -> wd a
withMouseDown wd a
wd = forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseDown forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> wd a
wd forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseUp

-- |Press and hold the left mouse button down. Note that undefined behavior
-- occurs if the next mouse command is not mouseUp.
mouseDown :: (HasCallStack, WebDriver wd) => wd ()
mouseDown :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseDown = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/buttondown" Value
Null

-- |Release the left mouse button.
mouseUp :: (HasCallStack, WebDriver wd) => wd ()
mouseUp :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
mouseUp = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/buttonup" Value
Null

-- |Double click at the current mouse location.
doubleClick :: (HasCallStack, WebDriver wd) => wd ()
doubleClick :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
doubleClick = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/doubleclick" Value
Null

-- |Single tap on the touch screen at the given element's location.
touchClick :: (HasCallStack, WebDriver wd) => Element -> wd ()
touchClick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
touchClick (Element Text
e) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/click" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"element" forall a b. (a -> b) -> a -> b
$ Text
e

-- |Emulates pressing a finger down on the screen at the given location.
touchDown :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchDown :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchDown = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/down" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")

-- |Emulates removing a finger from the screen at the given location.
touchUp :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchUp :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchUp = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/up" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")

-- |Emulates moving a finger on the screen to the given location.
touchMove :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchMove :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchMove = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/move" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"x",Text
"y")

-- |Emulate finger-based touch scroll. Use this function if you don't care where
-- the scroll begins
touchScroll :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchScroll :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchScroll = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/scroll" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"xoffset",Text
"yoffset")

-- |Emulate finger-based touch scroll, starting from the given location relative
-- to the given element.
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) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/scroll"
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c.
(ToJSON a, ToJSON b, ToJSON c) =>
(Text, Text, Text) -> (a, b, c) -> Value
triple (Text
"xoffset", Text
"yoffset", Text
"element")
  forall a b. (a -> b) -> a -> b
$ (Int
x, Int
y, Text
e)

-- |Emulate a double click on a touch device.
touchDoubleClick :: (HasCallStack, WebDriver wd) => Element -> wd ()
touchDoubleClick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
touchDoubleClick (Element Text
e) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/doubleclick"
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"element" forall a b. (a -> b) -> a -> b
$ Text
e

-- |Emulate a long click on a touch device.
touchLongClick :: (HasCallStack, WebDriver wd) => Element -> wd ()
touchLongClick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd ()
touchLongClick (Element Text
e) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/longclick"
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"element" forall a b. (a -> b) -> a -> b
$ Text
e
-- |Emulate a flick on the touch screen. The coordinates indicate x and y
-- velocity, respectively. Use this function if you don't care where the
-- flick starts.
touchFlick :: (HasCallStack, WebDriver wd) => (Int, Int) -> wd ()
touchFlick :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int) -> wd ()
touchFlick =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/flick"
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (ToJSON a, ToJSON b) => (Text, Text) -> (a, b) -> Value
pair (Text
"xSpeed", Text
"ySpeed")

-- |Emulate a flick on the touch screen.
touchFlickFrom :: (HasCallStack, WebDriver wd) =>
                  Int           -- ^ flick velocity
                  -> (Int, Int) -- ^ a location relative to the given element
                  -> Element    -- ^ the given element
                  -> wd ()
touchFlickFrom :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Int -> (Int, Int) -> Element -> wd ()
touchFlickFrom Int
s (Int
x,Int
y) (Element Text
e) =
  forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/touch/flick" forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
  [Key
"xoffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
x
  ,Key
"yoffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
y
  ,Key
"speed"   forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
s
  ,Key
"element" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
e
  ]

-- |Get the current geographical location of the device.
getLocation :: (HasCallStack, WebDriver wd) => wd (Int, Int, Int)
getLocation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
wd (Int, Int, Int)
getLocation = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/location" Value
Null
              forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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"

-- |Set the current geographical location of the device.
setLocation :: (HasCallStack, WebDriver wd) => (Int, Int, Int) -> wd ()
setLocation :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
(Int, Int, Int) -> wd ()
setLocation = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/location"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c.
(ToJSON a, ToJSON b, ToJSON c) =>
(Text, Text, Text) -> (a, b, c) -> Value
triple (Text
"latitude",
                        Text
"longitude",
                        Text
"altitude")

-- |Uploads a file from the local filesystem by its file path.
uploadFile :: (HasCallStack, WebDriver wd) => FilePath -> wd ()
uploadFile :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd ()
uploadFile String
path = forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Entry -> wd ()
uploadZipEntry forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase ([ZipOption] -> String -> IO Entry
readEntry [] String
path)

-- |Uploads a raw bytestring with associated file info.
uploadRawFile :: (HasCallStack, WebDriver wd) =>
                 FilePath          -- ^File path to use with this bytestring.
                 -> Integer        -- ^Modification time
                                   -- (in seconds since Unix epoch).
                 -> LBS.ByteString -- ^ The file contents as a lazy ByteString
                 -> wd ()
uploadRawFile :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> Integer -> ByteString -> wd ()
uploadRawFile String
path Integer
t ByteString
str = forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Entry -> wd ()
uploadZipEntry (String -> Integer -> ByteString -> Entry
toEntry String
path Integer
t ByteString
str)


-- |Lowest level interface to the file uploading mechanism.
-- This allows you to specify the exact details of
-- the zip entry sent across network.
uploadZipEntry :: (HasCallStack, WebDriver wd) => Entry -> wd ()
uploadZipEntry :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Entry -> wd ()
uploadZipEntry = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/file" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => Text -> a -> Value
single Text
"file"
                 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64.encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> ByteString
fromArchive forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Entry -> Archive -> Archive
`addEntryToArchive` Archive
emptyArchive)


-- |Get the current number of keys in a web storage area.
storageSize :: (HasCallStack, WebDriver wd) => WebStorageType -> wd Integer
storageSize :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> wd Integer
storageSize WebStorageType
s = 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

-- |Get a list of all keys from a web storage area.
getAllKeys :: (HasCallStack, WebDriver wd) => WebStorageType -> wd [Text]
getAllKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> wd [Text]
getAllKeys WebStorageType
s = forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodGet WebStorageType
s Text
"" Value
Null

-- |Delete all keys within a given web storage area.
deleteAllKeys :: (HasCallStack, WebDriver wd) => WebStorageType -> wd ()
deleteAllKeys :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> wd ()
deleteAllKeys WebStorageType
s = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodDelete WebStorageType
s Text
"" Value
Null

-- |An HTML 5 storage type
data WebStorageType = LocalStorage | SessionStorage
                    deriving (WebStorageType -> WebStorageType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebStorageType -> WebStorageType -> Bool
$c/= :: WebStorageType -> WebStorageType -> Bool
== :: WebStorageType -> WebStorageType -> Bool
$c== :: WebStorageType -> WebStorageType -> Bool
Eq, Int -> WebStorageType -> ShowS
[WebStorageType] -> ShowS
WebStorageType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebStorageType] -> ShowS
$cshowList :: [WebStorageType] -> ShowS
show :: WebStorageType -> String
$cshow :: WebStorageType -> String
showsPrec :: Int -> WebStorageType -> ShowS
$cshowsPrec :: Int -> WebStorageType -> ShowS
Show, Eq 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
min :: WebStorageType -> WebStorageType -> WebStorageType
$cmin :: WebStorageType -> WebStorageType -> WebStorageType
max :: WebStorageType -> WebStorageType -> WebStorageType
$cmax :: WebStorageType -> WebStorageType -> WebStorageType
>= :: WebStorageType -> WebStorageType -> Bool
$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
compare :: WebStorageType -> WebStorageType -> Ordering
$ccompare :: WebStorageType -> WebStorageType -> Ordering
Ord, WebStorageType
forall a. a -> a -> Bounded a
maxBound :: WebStorageType
$cmaxBound :: WebStorageType
minBound :: WebStorageType
$cminBound :: WebStorageType
Bounded, Int -> WebStorageType
WebStorageType -> Int
WebStorageType -> [WebStorageType]
WebStorageType -> WebStorageType
WebStorageType -> WebStorageType -> [WebStorageType]
WebStorageType
-> WebStorageType -> WebStorageType -> [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
enumFromThenTo :: WebStorageType
-> WebStorageType -> WebStorageType -> [WebStorageType]
$cenumFromThenTo :: WebStorageType
-> WebStorageType -> WebStorageType -> [WebStorageType]
enumFromTo :: WebStorageType -> WebStorageType -> [WebStorageType]
$cenumFromTo :: WebStorageType -> WebStorageType -> [WebStorageType]
enumFromThen :: WebStorageType -> WebStorageType -> [WebStorageType]
$cenumFromThen :: WebStorageType -> WebStorageType -> [WebStorageType]
enumFrom :: WebStorageType -> [WebStorageType]
$cenumFrom :: WebStorageType -> [WebStorageType]
fromEnum :: WebStorageType -> Int
$cfromEnum :: WebStorageType -> Int
toEnum :: Int -> WebStorageType
$ctoEnum :: Int -> WebStorageType
pred :: WebStorageType -> WebStorageType
$cpred :: WebStorageType -> WebStorageType
succ :: WebStorageType -> WebStorageType
$csucc :: WebStorageType -> WebStorageType
Enum)

-- |Get the value associated with a key in the given web storage area.
-- Unset keys result in empty strings, since the Web Storage spec
-- makes no distinction between the empty string and an undefined value.
getKey :: (HasCallStack, WebDriver wd) => WebStorageType -> Text ->  wd Text
getKey :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> Text -> wd Text
getKey WebStorageType
s Text
k = 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

-- |Set a key in the given web storage area.
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 = forall (wd :: * -> *) a b.
(WebDriver wd, ToJSON a, FromJSON b) =>
Method -> WebStorageType -> Text -> a -> wd b
doStorageCommand Method
methodPost WebStorageType
s Text
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ [Key
"key"   forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
k,
                                                      Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
v ]
-- |Delete a key in the given web storage area.
deleteKey :: (HasCallStack, WebDriver wd) => WebStorageType -> Text -> wd ()
deleteKey :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
WebStorageType -> Text -> wd ()
deleteKey WebStorageType
s Text
k = forall (wd :: * -> *). WebDriver wd => wd NoReturn -> wd ()
noReturn forall a b. (a -> b) -> a -> b
$ 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

-- |A wrapper around 'doSessCommand' to create web storage requests.
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 = 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"

-- |Get information from the server as a JSON 'Object'. For more information
-- about this object see
-- <https://github.com/SeleniumHQ/selenium/wiki/JsonWireProtocol#status>
serverStatus :: (WebDriver wd) => wd Value   -- todo: make this a record type
serverStatus :: forall (wd :: * -> *). WebDriver wd => wd Value
serverStatus = forall (wd :: * -> *) a b.
(WebDriver wd, HasCallStack, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doCommand Method
methodGet Text
"/status" Value
Null

-- |A record that represents a single log entry.
data LogEntry =
  LogEntry { LogEntry -> Integer
logTime  :: Integer  -- ^ timestamp for the log entry. The standard
                                  -- does not specify the epoch or the unit of
                                  -- time.
           , LogEntry -> LogLevel
logLevel :: LogLevel -- ^ log verbosity level
           , LogEntry -> Text
logMsg   :: Text
           }
  deriving (LogEntry -> LogEntry -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogEntry -> LogEntry -> Bool
$c/= :: LogEntry -> LogEntry -> Bool
== :: LogEntry -> LogEntry -> Bool
$c== :: LogEntry -> LogEntry -> Bool
Eq, Eq 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
min :: LogEntry -> LogEntry -> LogEntry
$cmin :: LogEntry -> LogEntry -> LogEntry
max :: LogEntry -> LogEntry -> LogEntry
$cmax :: LogEntry -> LogEntry -> LogEntry
>= :: LogEntry -> LogEntry -> Bool
$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
compare :: LogEntry -> LogEntry -> Ordering
$ccompare :: LogEntry -> LogEntry -> Ordering
Ord, Int -> LogEntry -> ShowS
[LogEntry] -> ShowS
LogEntry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogEntry] -> ShowS
$cshowList :: [LogEntry] -> ShowS
show :: LogEntry -> String
$cshow :: LogEntry -> String
showsPrec :: Int -> LogEntry -> ShowS
$cshowsPrec :: Int -> LogEntry -> ShowS
Show, ReadPrec [LogEntry]
ReadPrec LogEntry
Int -> ReadS LogEntry
ReadS [LogEntry]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LogEntry]
$creadListPrec :: ReadPrec [LogEntry]
readPrec :: ReadPrec LogEntry
$creadPrec :: ReadPrec LogEntry
readList :: ReadS [LogEntry]
$creadList :: ReadS [LogEntry]
readsPrec :: Int -> ReadS LogEntry
$creadsPrec :: Int -> ReadS LogEntry
Read)


instance FromJSON LogEntry where
  parseJSON :: Value -> Parser LogEntry
parseJSON (Object Object
o) =
    Integer -> LogLevel -> Text -> LogEntry
LogEntry forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"timestamp"
             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"level"
             forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a. a -> Maybe a -> a
fromMaybe Text
"" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"message")
  parseJSON Value
v = forall a. String -> Value -> Parser a
typeMismatch String
"LogEntry" Value
v

type LogType = String

-- |Retrieve the log buffer for a given log type. The server-side log buffer is reset after each request.
--
-- Which log types are available is server defined, but the wire protocol lists these as common log types:
-- client, driver, browser, server
getLogs :: (HasCallStack, WebDriver wd) => LogType -> wd [LogEntry]
getLogs :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
String -> wd [LogEntry]
getLogs String
t = forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/log" forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ [Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= String
t]

-- |Get a list of available log types.
getLogTypes :: (HasCallStack, WebDriver wd) => wd [LogType]
getLogTypes :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [String]
getLogTypes = 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$c/= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
== :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$c== :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
Eq, Int -> ApplicationCacheStatus
ApplicationCacheStatus -> Int
ApplicationCacheStatus -> [ApplicationCacheStatus]
ApplicationCacheStatus -> ApplicationCacheStatus
ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [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
enumFromThenTo :: ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [ApplicationCacheStatus]
$cenumFromThenTo :: ApplicationCacheStatus
-> ApplicationCacheStatus
-> ApplicationCacheStatus
-> [ApplicationCacheStatus]
enumFromTo :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
$cenumFromTo :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
enumFromThen :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
$cenumFromThen :: ApplicationCacheStatus
-> ApplicationCacheStatus -> [ApplicationCacheStatus]
enumFrom :: ApplicationCacheStatus -> [ApplicationCacheStatus]
$cenumFrom :: ApplicationCacheStatus -> [ApplicationCacheStatus]
fromEnum :: ApplicationCacheStatus -> Int
$cfromEnum :: ApplicationCacheStatus -> Int
toEnum :: Int -> ApplicationCacheStatus
$ctoEnum :: Int -> ApplicationCacheStatus
pred :: ApplicationCacheStatus -> ApplicationCacheStatus
$cpred :: ApplicationCacheStatus -> ApplicationCacheStatus
succ :: ApplicationCacheStatus -> ApplicationCacheStatus
$csucc :: ApplicationCacheStatus -> ApplicationCacheStatus
Enum, ApplicationCacheStatus
forall a. a -> a -> Bounded a
maxBound :: ApplicationCacheStatus
$cmaxBound :: ApplicationCacheStatus
minBound :: ApplicationCacheStatus
$cminBound :: ApplicationCacheStatus
Bounded, Eq 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
min :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
$cmin :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
max :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
$cmax :: ApplicationCacheStatus
-> ApplicationCacheStatus -> ApplicationCacheStatus
>= :: ApplicationCacheStatus -> ApplicationCacheStatus -> Bool
$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
compare :: ApplicationCacheStatus -> ApplicationCacheStatus -> Ordering
$ccompare :: ApplicationCacheStatus -> ApplicationCacheStatus -> Ordering
Ord, Int -> ApplicationCacheStatus -> ShowS
[ApplicationCacheStatus] -> ShowS
ApplicationCacheStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplicationCacheStatus] -> ShowS
$cshowList :: [ApplicationCacheStatus] -> ShowS
show :: ApplicationCacheStatus -> String
$cshow :: ApplicationCacheStatus -> String
showsPrec :: Int -> ApplicationCacheStatus -> ShowS
$cshowsPrec :: Int -> ApplicationCacheStatus -> ShowS
Show, ReadPrec [ApplicationCacheStatus]
ReadPrec ApplicationCacheStatus
Int -> ReadS ApplicationCacheStatus
ReadS [ApplicationCacheStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplicationCacheStatus]
$creadListPrec :: ReadPrec [ApplicationCacheStatus]
readPrec :: ReadPrec ApplicationCacheStatus
$creadPrec :: ReadPrec ApplicationCacheStatus
readList :: ReadS [ApplicationCacheStatus]
$creadList :: ReadS [ApplicationCacheStatus]
readsPrec :: Int -> ReadS ApplicationCacheStatus
$creadsPrec :: Int -> ReadS ApplicationCacheStatus
Read)

instance FromJSON ApplicationCacheStatus where
    parseJSON :: Value -> Parser ApplicationCacheStatus
parseJSON Value
val = do
        Integer
n <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
        case Integer
n :: Integer of
            Integer
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Uncached
            Integer
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Idle
            Integer
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Checking
            Integer
3 -> forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Downloading
            Integer
4 -> forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
UpdateReady
            Integer
5 -> forall (m :: * -> *) a. Monad m => a -> m a
return ApplicationCacheStatus
Obsolete
            Integer
err -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Invalid JSON for ApplicationCacheStatus: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
err

getApplicationCacheStatus :: (WebDriver wd) => wd ApplicationCacheStatus
getApplicationCacheStatus :: forall (wd :: * -> *). WebDriver wd => wd ApplicationCacheStatus
getApplicationCacheStatus = 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