webdriver-w3c-0.0.2: 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 transformer for building WebDriver sessions.

Synopsis

Documentation

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

Execute a WebDriverT session.

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

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

checkWebDriverT Source #

Arguments

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

Condense to IO

-> (q -> Bool)

Result check

-> WebDriverT eff t 
-> Property 

For testing with QuickCheck

data WebDriverTT (t :: (* -> *) -> * -> *) (eff :: * -> *) (a :: *) Source #

Wrapper type around HttpTT; a stack of error, reader, writer, state, and prompt monad transformers.

Instances
(Monad eff, Monad (t eff), MonadTrans t) => Monad (WebDriverTT t eff) Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Methods

(>>=) :: WebDriverTT t eff a -> (a -> WebDriverTT t eff b) -> WebDriverTT t eff b #

(>>) :: WebDriverTT t eff a -> WebDriverTT t eff b -> WebDriverTT t eff b #

return :: a -> WebDriverTT t eff a #

fail :: String -> WebDriverTT t eff a #

(Monad eff, Monad (t eff), MonadTrans t) => Functor (WebDriverTT t eff) Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Methods

fmap :: (a -> b) -> WebDriverTT t eff a -> WebDriverTT t eff b #

(<$) :: a -> WebDriverTT t eff b -> WebDriverTT t eff a #

(Monad eff, Monad (t eff), MonadTrans t) => Applicative (WebDriverTT t eff) Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Methods

pure :: a -> WebDriverTT t eff a #

(<*>) :: WebDriverTT t eff (a -> b) -> WebDriverTT t eff a -> WebDriverTT t eff b #

liftA2 :: (a -> b -> c) -> WebDriverTT t eff a -> WebDriverTT t eff b -> WebDriverTT t eff c #

(*>) :: WebDriverTT t eff a -> WebDriverTT t eff b -> WebDriverTT t eff b #

(<*) :: WebDriverTT t eff a -> WebDriverTT t eff b -> WebDriverTT t eff a #

(Monad eff, Monad (t eff), MonadTrans t) => Assert (WebDriverTT t eff) Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Methods

assert :: Assertion -> WebDriverTT t eff () Source #

execWebDriverTT :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverConfig eff -> WebDriverTT t eff a -> t eff (Either (E WDError) a, S WDState, W WDError WDLog) Source #

Execute a WebDriverTT session.

debugWebDriverTT :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverConfig eff -> WebDriverTT t eff a -> t eff (Either String a, AssertionSummary) Source #

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

checkWebDriverTT Source #

Arguments

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

Condense to IO

-> (q -> Bool)

Result check

-> WebDriverTT t eff a 
-> Property 

For testing with QuickCheck.

liftWebDriverTT :: (Monad eff, Monad (t eff), MonadTrans t) => t eff a -> WebDriverTT t eff a Source #

Lift a value from the inner transformed monad

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 :: (Monad eff, Monad (t eff), MonadTrans t) => (S WDState -> a) -> WebDriverTT t eff a Source #

Get a computed value from the state

modifyState :: (Monad eff, Monad (t eff), MonadTrans t) => (S WDState -> S WDState) -> WebDriverTT t eff () Source #

Mutate the state

fromEnv :: (Monad eff, Monad (t eff), MonadTrans t) => (R WDError WDLog WDEnv -> a) -> WebDriverTT t eff a Source #

Get a computed value from the environment

comment :: (Monad eff, Monad (t eff), MonadTrans t) => String -> WebDriverTT t eff () Source #

Write a comment to the log.

wait Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> Int

Wait time in milliseconds

-> WebDriverTT t eff () 

Suspend the current session. Handy when waiting for pages to load.

logDebug :: (Monad eff, Monad (t eff), MonadTrans t) => WDLog -> WebDriverTT t eff () Source #

logNotice :: (Monad eff, Monad (t eff), MonadTrans t) => WDLog -> WebDriverTT t eff () Source #

throwError :: (Monad eff, Monad (t eff), MonadTrans t) => WDError -> WebDriverTT t eff a Source #

throwJsonError :: (Monad eff, Monad (t eff), MonadTrans t) => JsonError -> WebDriverTT t eff a Source #

expect :: (Monad eff, Monad (t eff), MonadTrans t, Eq a, Show a) => a -> a -> WebDriverTT t eff a Source #

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

expectIs Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t, Show a) 
=> (a -> Bool) 
-> String

Human readable error label

-> a 
-> WebDriverTT t eff a 

For validating responses. Throws an UnexpectedValue error if the a argument does not satisfy the predicate.

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 :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (WDError -> WebDriverTT t eff a) -> WebDriverTT t eff a Source #

Rethrows other error types

catchJsonError :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (JsonError -> WebDriverTT t eff a) -> WebDriverTT t eff a Source #

Rethrows other error types

catchHttpException :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (HttpException -> WebDriverTT t eff a) -> WebDriverTT t eff a Source #

Rethrows other error types

catchIOException :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (IOException -> WebDriverTT t eff a) -> WebDriverTT t eff a Source #

Rethrows other error types

catchAnyError :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (WDError -> WebDriverTT t eff a) -> (HttpException -> WebDriverTT t eff a) -> (IOException -> WebDriverTT t eff a) -> (JsonError -> WebDriverTT t eff a) -> WebDriverTT t eff a Source #

Explicitly handle any of the error types thrown in WebDriverTT

parseJson :: (Monad eff, Monad (t eff), MonadTrans t) => ByteString -> WebDriverTT t eff Value Source #

May throw a JsonError.

lookupKeyJson :: (Monad eff, Monad (t eff), MonadTrans t) => Text -> Value -> WebDriverTT t eff Value Source #

May throw a JsonError.

constructFromJson :: (Monad eff, Monad (t eff), MonadTrans t, FromJSON a) => Value -> WebDriverTT t eff a Source #

May throw a JsonError.

httpGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse Source #

Capures HttpExceptions.

httpSilentGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse Source #

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

httpPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> WebDriverTT t eff HttpResponse Source #

Capures HttpExceptions.

httpSilentPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> WebDriverTT t eff HttpResponse Source #

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

httpDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse Source #

Capures HttpExceptions.

httpSilentDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse Source #

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

hPutStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => Handle -> String -> WebDriverTT t eff () Source #

Capures IOExceptions.

hPutStrLnBlocking :: (Monad eff, Monad (t eff), MonadTrans t) => MVar () -> Handle -> String -> WebDriverTT t eff () Source #

Capures IOExceptions.

getStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff String Source #

promptForString Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> String

Prompt text

-> WebDriverTT t eff String 

Prompt for input on stdin.

promptForSecret Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> String

Prompt text

-> WebDriverTT t eff String 

Prompt for input on stdin, but do not echo the typed characters back to the terminal -- handy for getting suuper secret info.

writeFilePath :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> ByteString -> WebDriverTT t eff () Source #

Captures IOExceptions

fileExists :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> WebDriverTT t eff Bool Source #

Captures IOExceptions

breakpointsOn :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff () Source #

breakpointsOff :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff () Source #

breakpoint :: (Monad eff, Monad (t eff), MonadTrans t) => String -> WebDriverTT t eff () Source #

breakpointWith :: (Monad eff, Monad (t eff), MonadTrans t) => String -> Maybe (String, WebDriverTT t eff ()) -> WebDriverTT t eff () Source #

Types

data E e #

Error type.

Instances
Show e => Show (E e) 
Instance details

Defined in Control.Monad.Script.Http

Methods

showsPrec :: Int -> E e -> ShowS #

show :: E e -> String #

showList :: [E e] -> ShowS #

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.

Instances
Eq JsonError 
Instance details

Defined in Data.Aeson.Extras

Show JsonError 
Instance details

Defined in Data.Aeson.Extras

Arbitrary JsonError 
Instance details

Defined in Data.Aeson.Extras

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

Instances
Eq ApiVersion Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Show ApiVersion Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

data Outcome Source #

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

Constructors

IsSuccess 
IsFailure 
Instances
Eq Outcome Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Methods

(==) :: Outcome -> Outcome -> Bool #

(/=) :: Outcome -> Outcome -> Bool #

Show Outcome Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

type Url = String #

To make type signatures nicer

data WDLog Source #

WebDriver specific log entries.

Instances
Show WDLog Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Methods

showsPrec :: Int -> WDLog -> ShowS #

show :: WDLog -> String #

showList :: [WDLog] -> ShowS #

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

Atomic effects

Constructors

HPutStrLn :: forall (p :: Type -> Type) a. Handle -> String -> P p (Either IOException ()) 
HPutStrLnBlocking :: forall (p :: Type -> Type) a. MVar () -> Handle -> String -> P p (Either IOException ()) 
GetSystemTime :: forall (p :: Type -> Type) a. P p UTCTime 
ThreadDelay :: forall (p :: Type -> Type) a. Int -> P p () 
HttpGet :: forall (p :: Type -> Type) a. Options -> Maybe Session -> Url -> P p (Either HttpException HttpResponse) 
HttpPost :: forall (p :: Type -> Type) a. Options -> Maybe Session -> Url -> ByteString -> P p (Either HttpException HttpResponse) 
HttpDelete :: forall (p :: Type -> Type) a. Options -> Maybe Session -> Url -> P p (Either HttpException HttpResponse) 
P :: forall (p :: Type -> Type) a. p a -> P p a 

data S s #

State type

Constructors

S 
Instances
Show s => Show (S s) 
Instance details

Defined in Control.Monad.Script.Http

Methods

showsPrec :: Int -> S s -> ShowS #

show :: S s -> String #

showList :: [S s] -> ShowS #

data WDState Source #

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

Instances
Show WDState Source # 
Instance details

Defined in Web.Api.WebDriver.Monad

Logs

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

Filter the assertions from a WebDriver log.

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

Extract the user-defined log entries.

printHttpLogs :: Handle -> Maybe (MVar ()) -> LogOptions e w -> (LogOptions e w -> LogEntry e w -> Maybe String) -> W e w -> IO () #

All log statements should go through logNow.

basicLogEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String #

Simple default pretty printer for LogEntrys.