webdriver-w3c-0.0.1: Bindings to the WebDriver API

Copyright2018 Automattic Inc.
LicenseGPL-3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Web.Api.WebDriver.Monad

Contents

Description

A monad and monad transformer for

Synopsis

Documentation

execWebDriver :: Monad eff => WebDriverConfig eff -> WebDriver eff a -> eff (Either (E WDError) a, S WDState, W WDError WDLog) Source #

Execute a WebDriver session.

debugWebDriver :: Monad eff => WebDriverConfig eff -> WebDriver eff a -> eff (Either String a, AssertionSummary) Source #

Execute a WebDriver session, returning an assertion summary with the result.

checkWebDriver Source #

Arguments

:: Monad eff 
=> WebDriverConfig eff 
-> (eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q)

Condense to IO

-> (q -> Bool)

Result check

-> WebDriver eff t 
-> Property 

For testing with QuickCheck

data WebDriverT m a Source #

Wrapper type around HttpT; a stack of error, reader, writer, state, and prompt monads.

Instances

Monad (WebDriverT m) Source # 

Methods

(>>=) :: WebDriverT m a -> (a -> WebDriverT m b) -> WebDriverT m b #

(>>) :: WebDriverT m a -> WebDriverT m b -> WebDriverT m b #

return :: a -> WebDriverT m a #

fail :: String -> WebDriverT m a #

Functor (WebDriverT m) Source # 

Methods

fmap :: (a -> b) -> WebDriverT m a -> WebDriverT m b #

(<$) :: a -> WebDriverT m b -> WebDriverT m a #

Applicative (WebDriverT m) Source # 

Methods

pure :: a -> WebDriverT m a #

(<*>) :: WebDriverT m (a -> b) -> WebDriverT m a -> WebDriverT m b #

liftA2 :: (a -> b -> c) -> WebDriverT m a -> WebDriverT m b -> WebDriverT m c #

(*>) :: WebDriverT m a -> WebDriverT m b -> WebDriverT m b #

(<*) :: WebDriverT m a -> WebDriverT m b -> WebDriverT m a #

Assert (WebDriverT m) Source # 

Methods

assert :: Assertion -> WebDriverT m () Source #

execWebDriverT Source #

Arguments

:: (Monad eff, Monad (m eff)) 
=> WebDriverConfig eff 
-> (forall u. eff u -> m eff u)

Lift effects to the inner monad

-> WebDriverT (m eff) a 
-> m eff (Either (E WDError) a, S WDState, W WDError WDLog) 

Execute a WebDriverT session.

debugWebDriverT Source #

Arguments

:: (Monad eff, Monad (m eff)) 
=> WebDriverConfig eff 
-> (forall u. eff u -> m eff u)

Lift effects to the inner monad

-> WebDriverT (m eff) a 
-> m eff (Either String a, AssertionSummary) 

Execute a WebDriverT session, returning an assertion summary with the result.

checkWebDriverT Source #

Arguments

:: (Monad eff, Monad (m eff)) 
=> WebDriverConfig eff 
-> (forall u. eff u -> m eff u)

Lift effects to the inner monad

-> (m eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q)

Condense to IO

-> (q -> Bool)

Result check

-> WebDriverT (m eff) t 
-> Property 

For testing with QuickCheck.

liftWebDriverT :: Monad m => m a -> WebDriverT m a Source #

Lift a value from the inner monad

newtype IdentityT m a Source #

The identity monad transformer.

Constructors

IdentityT 

Fields

Instances

Monad m => Monad (IdentityT m) Source # 

Methods

(>>=) :: IdentityT m a -> (a -> IdentityT m b) -> IdentityT m b #

(>>) :: IdentityT m a -> IdentityT m b -> IdentityT m b #

return :: a -> IdentityT m a #

fail :: String -> IdentityT m a #

Functor m => Functor (IdentityT m) Source # 

Methods

fmap :: (a -> b) -> IdentityT m a -> IdentityT m b #

(<$) :: a -> IdentityT m b -> IdentityT m a #

Monad m => Applicative (IdentityT m) Source # 

Methods

pure :: a -> IdentityT m a #

(<*>) :: IdentityT m (a -> b) -> IdentityT m a -> IdentityT m b #

liftA2 :: (a -> b -> c) -> IdentityT m a -> IdentityT m b -> IdentityT m c #

(*>) :: IdentityT m a -> IdentityT m b -> IdentityT m b #

(<*) :: IdentityT m a -> IdentityT m b -> IdentityT m a #

evalWDAct :: WDAct a -> IO a Source #

Standard IO evaluator for WDAct.

evalIO #

Arguments

:: (p a -> IO a)

Evaluator for user effects

-> P p a 
-> IO a 

Basic evaluator for interpreting atomic Http effects in IO.

evalWDActMockIO :: WDAct a -> MockIO u a Source #

Standard MockIO evaluator for WDAct.

evalMockIO :: (p a -> MockIO s a) -> P p a -> MockIO s a #

Basic evaluator for interpreting atomic Http effects in MockIO.

Config

data WebDriverConfig eff Source #

Type representing configuration settings for a WebDriver session

Constructors

WDConfig 

Fields

defaultWDEnv :: WDEnv Source #

Uses default geckodriver settings

defaultWebDriverLogOptions :: LogOptions WDError WDLog Source #

Noisy, JSON, in color, without headers.

API

fromState :: (S WDState -> a) -> WebDriverT m a Source #

Get a computed value from the state

modifyState :: (S WDState -> S WDState) -> WebDriverT m () Source #

Mutate the state

fromEnv :: (R WDError WDLog WDEnv -> a) -> WebDriverT m a Source #

Get a computed value from the environment

comment :: String -> WebDriverT m () Source #

Write a comment to the log.

wait :: Int -> WebDriverT m () Source #

In milliseconds

expect :: (Monad m, Eq a, Show a) => a -> a -> WebDriverT m a Source #

For validating responses. Throws an UnexpectedValue error if the two arguments are not equal according to their Eq instance.

assert :: Assert m => Assertion -> m () Source #

Make an assertion. Typically m is a monad, and the Assert instance handles the assertion in m by e.g. logging it, changing state, etc.

catchError :: WebDriverT m a -> (WDError -> WebDriverT m a) -> WebDriverT m a Source #

Rethrows other error types

catchJsonError :: WebDriverT m a -> (JsonError -> WebDriverT m a) -> WebDriverT m a Source #

Rethrows other error types

catchHttpException :: WebDriverT m a -> (HttpException -> WebDriverT m a) -> WebDriverT m a Source #

Rethrows other error types

catchIOException :: WebDriverT m a -> (IOException -> WebDriverT m a) -> WebDriverT m a Source #

Rethrows other error types

parseJson :: ByteString -> WebDriverT m Value Source #

May throw a JsonError.

lookupKeyJson :: Text -> Value -> WebDriverT m Value Source #

May throw a JsonError.

constructFromJson :: FromJSON a => Value -> WebDriverT m a Source #

May throw a JsonError.

httpGet :: Url -> WebDriverT m HttpResponse Source #

Capures HttpExceptions.

httpSilentGet :: Url -> WebDriverT m HttpResponse Source #

Does not write request or response info to the log, except to note that a request occurred. Capures HttpExceptions.

httpPost :: Url -> ByteString -> WebDriverT m HttpResponse Source #

Capures HttpExceptions.

httpSilentPost :: Url -> ByteString -> WebDriverT m HttpResponse Source #

Does not write request or response info to the log, except to note that a request occurred. Capures HttpExceptions.

httpDelete :: Url -> WebDriverT m HttpResponse Source #

Capures HttpExceptions.

httpSilentDelete :: Url -> WebDriverT m HttpResponse Source #

Does not write request or response info to the log, except to note that a request occurred. Capures HttpExceptions.

Types

data E e :: * -> * #

Error type.

data JsonError :: * #

Represents the kinds of errors that can occur when parsing and decoding JSON.

Constructors

JsonError String

A generic JSON error; try not to use this.

JsonParseError ByteString

A failed parse.

JsonKeyDoesNotExist Text Value

An attempt to look up the value of a key that does not exist on an object.

JsonKeyLookupOffObject Text Value

An attempt to look up the value of a key on something other than an object.

JsonConstructError String

A failed attempt to convert a Value to some other type.

data R e w r :: * -> * -> * -> * #

Generic session environment.

Constructors

R 

Fields

data LogOptions e w :: * -> * -> * #

Options for tweaking the logs.

Constructors

LogOptions 

Fields

data WDEnv Source #

Read-only environment variables specific to WebDriver.

Constructors

WDEnv 

Fields

data ResponseFormat Source #

Format flag for HTTP responses from the remote end. Chromedriver, for instance, is not spec-compliant. :)

Constructors

SpecFormat

Responses as described in the spec.

ChromeFormat

Responses as emitted by chromedriver.

data ApiVersion Source #

Version of the WebDriver specification.

Constructors

CR_2018_03_04

Candidate Recommendation, March 4, 2018

data Outcome Source #

Type representing an abstract outcome. Do with it what you will.

Constructors

IsSuccess 
IsFailure 

type Url = String #

To make type signatures nicer

data WDLog Source #

WebDriver specific log entries.

Instances

data P (p :: * -> *) a :: (* -> *) -> * -> * where #

Atomic effects

data S s :: * -> * #

State type

Constructors

S 

newtype WDState Source #

Includes a Maybe String representing the current session ID, if one has been opened.

Constructors

WDState 

Instances

Logs

getAssertions :: [WDLog] -> [Assertion] Source #

Filter the assertions from a WebDriver log.

logEntries :: W e w -> [w] #

Extract the user-defined log entries.