| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Test.WebDriver.Types
Synopsis
- data WebDriverContext = WebDriverContext {}
- mkEmptyWebDriverContext :: MonadIO m => m WebDriverContext
- data Driver = Driver {}
- data DriverConfig- = DriverConfigSeleniumJar { }
- | DriverConfigGeckodriver { }
- | DriverConfigChromedriver { }
 
- data SeleniumVersion
- class SessionState (m :: Type -> Type) where- getSession :: m Session
 
- class SessionState m => SessionStatePut (m :: Type -> Type) where- withModifiedSession :: (Session -> Session) -> m a -> m a
 
- newtype SessionId = SessionId Text
- data Session = Session {}
- data SessionException
- data StackFrame = StackFrame {}
- callStackItemToStackFrame :: (String, SrcLoc) -> StackFrame
- type WebDriver (m :: Type -> Type) = (WebDriverBase m, SessionState m)
- class MonadUnliftIO m => WebDriverBase (m :: Type -> Type) where- doCommandBase :: (HasCallStack, ToJSON a) => Driver -> Method -> Text -> a -> m (Response ByteString)
 
- type Method = ByteString
- methodDelete :: Method
- methodGet :: Method
- methodPost :: Method
Documentation
data WebDriverContext Source #
The WebDriverContext is an opaque type used by this library for
 bookkeeping purposes. It tracks all the processes we spin up and all the
 sessions we create.
Currently, we will create at most 1 Selenium or Chromedriver process per
 WebDriverContext, and N Geckodriver processes, where N is the number of
 Firefox sessions you request.
Constructors
| WebDriverContext | |
| Fields 
 | |
mkEmptyWebDriverContext :: MonadIO m => m WebDriverContext Source #
Create a new WebDriverContext.
Constructors
| Driver | |
| Fields | |
data DriverConfig Source #
Configuration for how to launch a given driver.
Constructors
| DriverConfigSeleniumJar | For launching a WebDriver via "java -jar selenium.jar".
 Selenium can launch other drivers on your behalf. You should pass these as  | 
| Fields 
 | |
| DriverConfigGeckodriver | |
| Fields 
 | |
| DriverConfigChromedriver | |
| Fields 
 | |
data SeleniumVersion Source #
Instances
| Show SeleniumVersion Source # | |
| Defined in Test.WebDriver.Types Methods showsPrec :: Int -> SeleniumVersion -> ShowS # show :: SeleniumVersion -> String # showList :: [SeleniumVersion] -> ShowS # | |
| Eq SeleniumVersion Source # | |
| Defined in Test.WebDriver.Types Methods (==) :: SeleniumVersion -> SeleniumVersion -> Bool # (/=) :: SeleniumVersion -> SeleniumVersion -> Bool # | |
SessionState class
class SessionState (m :: Type -> Type) where Source #
Methods
getSession :: m Session Source #
class SessionState m => SessionStatePut (m :: Type -> Type) where Source #
Methods
withModifiedSession :: (Session -> Session) -> m a -> m a Source #
WebDriver sessions
An opaque identifier for a WebDriver session. These handles are produced by the server on session creation, and act to identify a session in progress.
Instances
| FromJSON SessionId Source # | |
| Defined in Test.WebDriver.Types | |
| ToJSON SessionId Source # | |
| IsString SessionId Source # | |
| Defined in Test.WebDriver.Types Methods fromString :: String -> SessionId # | |
| Read SessionId Source # | |
| Show SessionId Source # | |
| Eq SessionId Source # | |
| Ord SessionId Source # | |
Constructors
| Session | |
| Fields | |
Exceptions
data SessionException Source #
Constructors
| SessionNameAlreadyExists | |
| SessionCreationFailed (Response ByteString) | |
| SessionCreationResponseHadNoSessionId (Response ByteString) | 
Instances
| Exception SessionException Source # | |
| Defined in Test.WebDriver.Types Methods toException :: SessionException -> SomeException # | |
| Show SessionException Source # | |
| Defined in Test.WebDriver.Types Methods showsPrec :: Int -> SessionException -> ShowS # show :: SessionException -> String # showList :: [SessionException] -> ShowS # | |
Stack frames
data StackFrame Source #
An individual stack frame from the stack trace provided by the server during a FailedCommand.
Constructors
| StackFrame | |
| Fields 
 | |
Instances
| FromJSON StackFrame Source # | |
| Defined in Test.WebDriver.Types | |
| Show StackFrame Source # | |
| Defined in Test.WebDriver.Types Methods showsPrec :: Int -> StackFrame -> ShowS # show :: StackFrame -> String # showList :: [StackFrame] -> ShowS # | |
| Eq StackFrame Source # | |
| Defined in Test.WebDriver.Types | |
callStackItemToStackFrame :: (String, SrcLoc) -> StackFrame Source #
WebDriver class
type WebDriver (m :: Type -> Type) = (WebDriverBase m, SessionState m) Source #
class MonadUnliftIO m => WebDriverBase (m :: Type -> Type) where Source #
A class for monads that can handle wire protocol requests. This is the operation underlying all of the high-level commands exported in Test.WebDriver.Commands.
Methods
Arguments
| :: (HasCallStack, ToJSON a) | |
| => Driver | |
| -> Method | HTTP request method | 
| -> Text | URL of request | 
| -> a | JSON parameters passed in the body of the request. Note that, as a special case, anything that converts to Data.Aeson.Null will result in an empty request body. | 
| -> m (Response ByteString) | The response of the HTTP request. | 
type Method = ByteString #
HTTP method (flat ByteString type).
methodDelete :: Method #
HTTP DELETE Method
methodPost :: Method #
HTTP POST Method