Copyright | 2018 Automattic Inc. |
---|---|
License | GPL-3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
A monad transformer for building WebDriver sessions.
Synopsis
- type WebDriverT eff a = WebDriverTT IdentityT eff a
- execWebDriverT :: Monad eff => WebDriverConfig eff -> WebDriverT eff a -> eff (Either (E WDError) a, S WDState, W WDError WDLog)
- debugWebDriverT :: Monad eff => WebDriverConfig eff -> WebDriverT eff a -> eff (Either String a, AssertionSummary)
- checkWebDriverT :: (Monad eff, Show q) => WebDriverConfig eff -> (eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q) -> (q -> Bool) -> WebDriverT eff t -> Property
- data WebDriverTT (t :: (* -> *) -> * -> *) (eff :: * -> *) (a :: *)
- 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)
- debugWebDriverTT :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverConfig eff -> WebDriverTT t eff a -> t eff (Either String a, AssertionSummary)
- checkWebDriverTT :: (Monad eff, Monad (t eff), MonadTrans t, Show q) => WebDriverConfig eff -> (t eff (Either (E WDError) a, S WDState, W WDError WDLog) -> IO q) -> (q -> Bool) -> WebDriverTT t eff a -> Property
- liftWebDriverTT :: (Monad eff, Monad (t eff), MonadTrans t) => t eff a -> WebDriverTT t eff a
- evalWDAct :: WDAct a -> IO a
- evalIO :: (p a -> IO a) -> P p a -> IO a
- evalWDActMockIO :: WDAct a -> MockIO u a
- evalMockIO :: (p a -> MockIO s a) -> P p a -> MockIO s a
- data WebDriverConfig eff = WDConfig {
- _initialState :: S WDState
- _environment :: R WDError WDLog WDEnv
- _evaluator :: forall a. P WDAct a -> eff a
- defaultWebDriverConfig :: WebDriverConfig IO
- defaultWebDriverState :: S WDState
- defaultWebDriverEnvironment :: R WDError WDLog WDEnv
- defaultWDEnv :: WDEnv
- defaultWebDriverLogOptions :: LogOptions WDError WDLog
- fromState :: (Monad eff, Monad (t eff), MonadTrans t) => (S WDState -> a) -> WebDriverTT t eff a
- modifyState :: (Monad eff, Monad (t eff), MonadTrans t) => (S WDState -> S WDState) -> WebDriverTT t eff ()
- fromEnv :: (Monad eff, Monad (t eff), MonadTrans t) => (R WDError WDLog WDEnv -> a) -> WebDriverTT t eff a
- comment :: (Monad eff, Monad (t eff), MonadTrans t) => String -> WebDriverTT t eff ()
- wait :: (Monad eff, Monad (t eff), MonadTrans t) => Int -> WebDriverTT t eff ()
- logDebug :: (Monad eff, Monad (t eff), MonadTrans t) => WDLog -> WebDriverTT t eff ()
- logNotice :: (Monad eff, Monad (t eff), MonadTrans t) => WDLog -> WebDriverTT t eff ()
- throwError :: (Monad eff, Monad (t eff), MonadTrans t) => WDError -> WebDriverTT t eff a
- throwJsonError :: (Monad eff, Monad (t eff), MonadTrans t) => JsonError -> WebDriverTT t eff a
- throwHttpException :: (Monad eff, Monad (t eff), MonadTrans t) => HttpException -> WebDriverTT t eff a
- throwIOException :: (Monad eff, Monad (t eff), MonadTrans t) => IOException -> WebDriverTT t eff a
- expect :: (Monad eff, Monad (t eff), MonadTrans t, Eq a, Show a) => a -> a -> WebDriverTT t eff a
- expectIs :: (Monad eff, Monad (t eff), MonadTrans t, Show a) => (a -> Bool) -> String -> a -> WebDriverTT t eff a
- assert :: Assert m => Assertion -> m ()
- catchError :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (WDError -> WebDriverTT t eff a) -> WebDriverTT t eff a
- catchJsonError :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (JsonError -> WebDriverTT t eff a) -> WebDriverTT t eff a
- catchHttpException :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (HttpException -> WebDriverTT t eff a) -> WebDriverTT t eff a
- catchIOException :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff a -> (IOException -> WebDriverTT t eff a) -> WebDriverTT t eff a
- 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
- parseJson :: (Monad eff, Monad (t eff), MonadTrans t) => ByteString -> WebDriverTT t eff Value
- lookupKeyJson :: (Monad eff, Monad (t eff), MonadTrans t) => Text -> Value -> WebDriverTT t eff Value
- constructFromJson :: (Monad eff, Monad (t eff), MonadTrans t, FromJSON a) => Value -> WebDriverTT t eff a
- httpGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse
- httpSilentGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse
- httpPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> WebDriverTT t eff HttpResponse
- httpSilentPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> WebDriverTT t eff HttpResponse
- httpDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse
- httpSilentDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse
- hPutStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => Handle -> String -> WebDriverTT t eff ()
- hPutStrLnBlocking :: (Monad eff, Monad (t eff), MonadTrans t) => MVar () -> Handle -> String -> WebDriverTT t eff ()
- getStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff String
- promptForString :: (Monad eff, Monad (t eff), MonadTrans t) => String -> WebDriverTT t eff String
- promptForSecret :: (Monad eff, Monad (t eff), MonadTrans t) => String -> WebDriverTT t eff String
- readFilePath :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> WebDriverTT t eff ByteString
- writeFilePath :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> ByteString -> WebDriverTT t eff ()
- fileExists :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> WebDriverTT t eff Bool
- breakpointsOn :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff ()
- breakpointsOff :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff ()
- breakpoint :: (Monad eff, Monad (t eff), MonadTrans t) => String -> WebDriverTT t eff ()
- breakpointWith :: (Monad eff, Monad (t eff), MonadTrans t) => String -> Maybe (String, WebDriverTT t eff ()) -> WebDriverTT t eff ()
- data E e
- data JsonError
- data WDError
- data R e w r = R {
- _logOptions :: LogOptions e w
- _logEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String
- _logHandle :: Handle
- _logLock :: Maybe (MVar ())
- _uid :: String
- _httpErrorInject :: HttpException -> Maybe e
- _env :: r
- data LogOptions e w = LogOptions {
- _logColor :: Bool
- _logJson :: Bool
- _logSilent :: Bool
- _logMinSeverity :: LogSeverity
- _logHeaders :: Bool
- _printUserError :: Bool -> e -> String
- _printUserLog :: Bool -> w -> String
- data WDEnv = WDEnv {}
- data ResponseFormat
- data ApiVersion = CR_2018_03_04
- data Outcome
- type Url = String
- data HttpResponse = HttpResponse {}
- data WDLog
- = LogAssertion Assertion
- | LogSession SessionVerb
- | LogUnexpectedResult Outcome String
- | LogBreakpoint String
- data P (p :: Type -> Type) a where
- 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 WDAct a where
- ReadFilePath :: FilePath -> WDAct (Either IOException ByteString)
- WriteFilePath :: FilePath -> ByteString -> WDAct (Either IOException ())
- FileExists :: FilePath -> WDAct (Either IOException Bool)
- HGetLine :: Handle -> WDAct (Either IOException String)
- HGetLineNoEcho :: Handle -> WDAct (Either IOException String)
- data S s = S {
- _httpOptions :: Options
- _httpSession :: Maybe Session
- _userState :: s
- data WDState = WDState {}
- data BreakpointSetting
- getAssertions :: [WDLog] -> [Assertion]
- logEntries :: W e w -> [w]
- printHttpLogs :: Handle -> Maybe (MVar ()) -> LogOptions e w -> (LogOptions e w -> LogEntry e w -> Maybe String) -> W e w -> IO ()
- basicLogEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String
Documentation
type WebDriverT eff a = WebDriverTT IdentityT eff a Source #
WebDriverTT
over IdentityT
.
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.
:: (Monad eff, Show q) | |
=> WebDriverConfig eff | |
-> (eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q) | Condense to |
-> (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
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.
:: (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 |
-> (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
Basic evaluator for interpreting atomic Http
effects in IO
.
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
WDConfig | |
|
defaultWebDriverConfig :: WebDriverConfig IO Source #
Default IO
effects
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.
:: (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 #
throwHttpException :: (Monad eff, Monad (t eff), MonadTrans t) => HttpException -> WebDriverTT t eff a Source #
throwIOException :: (Monad eff, Monad (t eff), MonadTrans t) => IOException -> 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.
:: (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 HttpException
s.
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 HttpException
s.
httpPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> WebDriverTT t eff HttpResponse Source #
Capures HttpException
s.
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 HttpException
s.
httpDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> WebDriverTT t eff HttpResponse Source #
Capures HttpException
s.
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 HttpException
s.
hPutStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => Handle -> String -> WebDriverTT t eff () Source #
Capures IOException
s.
hPutStrLnBlocking :: (Monad eff, Monad (t eff), MonadTrans t) => MVar () -> Handle -> String -> WebDriverTT t eff () Source #
Capures IOException
s.
getStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => WebDriverTT t eff String Source #
:: (Monad eff, Monad (t eff), MonadTrans t) | |
=> String | Prompt text |
-> WebDriverTT t eff String |
Prompt for input on stdin
.
:: (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.
readFilePath :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> WebDriverTT t eff ByteString Source #
Captures IOException
s
writeFilePath :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> ByteString -> WebDriverTT t eff () Source #
Captures IOException
s
fileExists :: (Monad eff, Monad (t eff), MonadTrans t) => FilePath -> WebDriverTT t eff Bool Source #
Captures IOException
s
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
Error type.
Represents the kinds of errors that can occur when parsing and decoding JSON.
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 |
Errors specific to WebDriver sessions.
Generic session environment.
R | |
|
data LogOptions e w #
Options for tweaking the logs.
LogOptions | |
|
Read-only environment variables specific to WebDriver.
WDEnv | |
|
data ResponseFormat Source #
Format flag for HTTP responses from the remote end. Chromedriver, for instance, is not spec-compliant. :)
SpecFormat | Responses as described in the spec. |
ChromeFormat | Responses as emitted by chromedriver. |
Instances
Eq ResponseFormat Source # | |
Defined in Web.Api.WebDriver.Monad (==) :: ResponseFormat -> ResponseFormat -> Bool # (/=) :: ResponseFormat -> ResponseFormat -> Bool # | |
Show ResponseFormat Source # | |
Defined in Web.Api.WebDriver.Monad showsPrec :: Int -> ResponseFormat -> ShowS # show :: ResponseFormat -> String # showList :: [ResponseFormat] -> ShowS # |
data ApiVersion Source #
Version of the WebDriver specification.
CR_2018_03_04 | Candidate Recommendation, March 4, 2018 |
Instances
Eq ApiVersion Source # | |
Defined in Web.Api.WebDriver.Monad (==) :: ApiVersion -> ApiVersion -> Bool # (/=) :: ApiVersion -> ApiVersion -> Bool # | |
Show ApiVersion Source # | |
Defined in Web.Api.WebDriver.Monad showsPrec :: Int -> ApiVersion -> ShowS # show :: ApiVersion -> String # showList :: [ApiVersion] -> ShowS # |
Type representing an abstract outcome. Do with it what you will.
data HttpResponse #
Non-opaque HTTP response type.
Instances
Eq HttpResponse | |
Defined in Network.HTTP.Client.Extras (==) :: HttpResponse -> HttpResponse -> Bool # (/=) :: HttpResponse -> HttpResponse -> Bool # | |
Show HttpResponse | |
Defined in Network.HTTP.Client.Extras showsPrec :: Int -> HttpResponse -> ShowS # show :: HttpResponse -> String # showList :: [HttpResponse] -> ShowS # |
WebDriver specific log entries.
data P (p :: Type -> Type) a where #
Atomic effects
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 |
WebDriver specific effects
ReadFilePath :: FilePath -> WDAct (Either IOException ByteString) | |
WriteFilePath :: FilePath -> ByteString -> WDAct (Either IOException ()) | |
FileExists :: FilePath -> WDAct (Either IOException Bool) | |
HGetLine :: Handle -> WDAct (Either IOException String) | |
HGetLineNoEcho :: Handle -> WDAct (Either IOException String) |
State type
S | |
|
Includes a Maybe String
representing the current session ID, if one has been opened.
data BreakpointSetting Source #
Instances
Eq BreakpointSetting Source # | |
Defined in Web.Api.WebDriver.Monad (==) :: BreakpointSetting -> BreakpointSetting -> Bool # (/=) :: BreakpointSetting -> BreakpointSetting -> Bool # | |
Show BreakpointSetting Source # | |
Defined in Web.Api.WebDriver.Monad showsPrec :: Int -> BreakpointSetting -> ShowS # show :: BreakpointSetting -> String # showList :: [BreakpointSetting] -> ShowS # |
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 LogEntry
s.