Copyright | 2018 Automattic Inc. |
---|---|
License | GPL-3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
A monad and monad transformer for
- type WebDriver eff a = WebDriverT (IdentityT eff) a
- execWebDriver :: Monad eff => WebDriverConfig eff -> WebDriver eff a -> eff (Either (E WDError) a, S WDState, W WDError WDLog)
- debugWebDriver :: Monad eff => WebDriverConfig eff -> WebDriver eff a -> eff (Either String a, AssertionSummary)
- checkWebDriver :: Monad eff => WebDriverConfig eff -> (eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q) -> (q -> Bool) -> WebDriver eff t -> Property
- data WebDriverT m a
- execWebDriverT :: (Monad eff, Monad (m eff)) => WebDriverConfig eff -> (forall u. eff u -> m eff u) -> WebDriverT (m eff) a -> m eff (Either (E WDError) a, S WDState, W WDError WDLog)
- debugWebDriverT :: (Monad eff, Monad (m eff)) => WebDriverConfig eff -> (forall u. eff u -> m eff u) -> WebDriverT (m eff) a -> m eff (Either String a, AssertionSummary)
- checkWebDriverT :: (Monad eff, Monad (m eff)) => WebDriverConfig eff -> (forall u. eff u -> m eff u) -> (m eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q) -> (q -> Bool) -> WebDriverT (m eff) t -> Property
- liftWebDriverT :: Monad m => m a -> WebDriverT m a
- newtype IdentityT m a = IdentityT {
- runIdentityT :: m 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 :: (S WDState -> a) -> WebDriverT m a
- modifyState :: (S WDState -> S WDState) -> WebDriverT m ()
- fromEnv :: (R WDError WDLog WDEnv -> a) -> WebDriverT m a
- comment :: String -> WebDriverT m ()
- wait :: Int -> WebDriverT m ()
- throwError :: WDError -> WebDriverT m a
- throwJsonError :: JsonError -> WebDriverT m a
- throwHttpException :: HttpException -> WebDriverT m a
- throwIOException :: IOException -> WebDriverT m a
- expect :: (Monad m, Eq a, Show a) => a -> a -> WebDriverT m a
- assert :: Assert m => Assertion -> m ()
- catchError :: WebDriverT m a -> (WDError -> WebDriverT m a) -> WebDriverT m a
- catchJsonError :: WebDriverT m a -> (JsonError -> WebDriverT m a) -> WebDriverT m a
- catchHttpException :: WebDriverT m a -> (HttpException -> WebDriverT m a) -> WebDriverT m a
- catchIOException :: WebDriverT m a -> (IOException -> WebDriverT m a) -> WebDriverT m a
- parseJson :: ByteString -> WebDriverT m Value
- lookupKeyJson :: Text -> Value -> WebDriverT m Value
- constructFromJson :: FromJSON a => Value -> WebDriverT m a
- httpGet :: Url -> WebDriverT m HttpResponse
- httpSilentGet :: Url -> WebDriverT m HttpResponse
- httpPost :: Url -> ByteString -> WebDriverT m HttpResponse
- httpSilentPost :: Url -> ByteString -> WebDriverT m HttpResponse
- httpDelete :: Url -> WebDriverT m HttpResponse
- httpSilentDelete :: Url -> WebDriverT m HttpResponse
- hPutStrLn :: Handle -> String -> WebDriverT m ()
- hPutStrLnBlocking :: MVar () -> Handle -> String -> WebDriverT m ()
- readFilePath :: Monad m => FilePath -> WebDriverT m ByteString
- writeFilePath :: Monad m => FilePath -> ByteString -> WebDriverT m ()
- fileExists :: Monad m => FilePath -> WebDriverT m Bool
- data E e :: * -> *
- data JsonError :: *
- data WDError
- data R e w r :: * -> * -> * -> * = R {
- _logOptions :: LogOptions e w
- _logHandle :: Handle
- _logLock :: Maybe (MVar ())
- _uid :: String
- _httpErrorInject :: HttpException -> Maybe e
- _env :: r
- data LogOptions e w :: * -> * -> * = LogOptions {
- _logColor :: Bool
- _logJson :: Bool
- _logSilent :: Bool
- _logHeaders :: Bool
- _logEntryPrinter :: (String -> String) -> (String, String, String) -> String
- _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
- data P (p :: * -> *) a :: (* -> *) -> * -> * where
- HPutStrLn :: P p (Either IOException ())
- HPutStrLnBlocking :: P p (Either IOException ())
- GetSystemTime :: P p UTCTime
- ThreadDelay :: P p ()
- HttpGet :: P p (Either HttpException HttpResponse)
- HttpPost :: P p (Either HttpException HttpResponse)
- HttpDelete :: P p (Either HttpException HttpResponse)
- P :: 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
- newtype WDState = WDState {}
- getAssertions :: [WDLog] -> [Assertion]
- logEntries :: W e w -> [w]
Documentation
type WebDriver eff a = WebDriverT (IdentityT eff) a Source #
WebDriverT
over IdentityT
.
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.
:: Monad eff | |
=> WebDriverConfig eff | |
-> (eff (Either (E WDError) t, S WDState, W WDError WDLog) -> IO q) | Condense to |
-> (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.
Monad (WebDriverT m) Source # | |
Functor (WebDriverT m) Source # | |
Applicative (WebDriverT m) Source # | |
Assert (WebDriverT m) Source # | |
:: (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.
:: (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.
:: (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 |
-> (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
evalMockIO :: (p a -> MockIO s a) -> P p a -> MockIO s a #
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
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
throwError :: WDError -> WebDriverT m a Source #
throwJsonError :: JsonError -> WebDriverT m a Source #
throwHttpException :: HttpException -> WebDriverT m a Source #
throwIOException :: IOException -> WebDriverT m a Source #
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 HttpException
s.
httpSilentGet :: Url -> WebDriverT m HttpResponse Source #
Does not write request or response info to the log, except to note that a request occurred. Capures HttpException
s.
httpPost :: Url -> ByteString -> WebDriverT m HttpResponse Source #
Capures HttpException
s.
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 HttpException
s.
httpDelete :: Url -> WebDriverT m HttpResponse Source #
Capures HttpException
s.
httpSilentDelete :: Url -> WebDriverT m HttpResponse Source #
Does not write request or response info to the log, except to note that a request occurred. Capures HttpException
s.
hPutStrLn :: Handle -> String -> WebDriverT m () Source #
Capures IOException
s.
hPutStrLnBlocking :: MVar () -> Handle -> String -> WebDriverT m () Source #
Capures IOException
s.
readFilePath :: Monad m => FilePath -> WebDriverT m ByteString Source #
Captures IOException
s
writeFilePath :: Monad m => FilePath -> ByteString -> WebDriverT m () Source #
Captures IOException
s
fileExists :: Monad m => FilePath -> WebDriverT m Bool Source #
Captures IOException
s
Types
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.
data R e w r :: * -> * -> * -> * #
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. |
data ApiVersion Source #
Version of the WebDriver specification.
CR_2018_03_04 | Candidate Recommendation, March 4, 2018 |
Type representing an abstract outcome. Do with it what you will.
WebDriver specific log entries.
LogAssertion Assertion | |
LogSession SessionVerb | |
LogUnexpectedResult Outcome String |
data P (p :: * -> *) a :: (* -> *) -> * -> * where #
Atomic effects
HPutStrLn :: P p (Either IOException ()) | |
HPutStrLnBlocking :: P p (Either IOException ()) | |
GetSystemTime :: P p UTCTime | |
ThreadDelay :: P p () | |
HttpGet :: P p (Either HttpException HttpResponse) | |
HttpPost :: P p (Either HttpException HttpResponse) | |
HttpDelete :: P p (Either HttpException HttpResponse) | |
P :: 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.
Logs
logEntries :: W e w -> [w] #
Extract the user-defined log entries.