Safe Haskell | None |
---|---|
Language | Haskell98 |
- waitUntil :: WDSessionStateControl m => Double -> m a -> m a
- waitUntil' :: WDSessionStateControl m => Int -> Double -> m a -> m a
- waitWhile :: WDSessionStateControl m => Double -> m a -> m ()
- waitWhile' :: WDSessionStateControl m => Int -> Double -> m a -> m ()
- data ExpectFailed
- expect :: MonadBaseControl IO m => Bool -> m ()
- unexpected :: MonadBaseControl IO m => String -> m a
- expectAny :: (Foldable f, MonadBaseControl IO m) => (a -> m Bool) -> f a -> m ()
- expectAll :: (Foldable f, MonadBaseControl IO m) => (a -> m Bool) -> f a -> m ()
- expectNotStale :: WebDriver wd => Element -> wd Element
- expectAlertOpen :: WebDriver wd => wd Text
- catchFailedCommand :: MonadBaseControl IO m => FailedCommandType -> m a -> m a
- onTimeout :: MonadBaseControl IO m => m a -> m a -> m a
Wait on expected conditions
waitUntil :: WDSessionStateControl m => Double -> m a -> m a Source
Wait until either the given action succeeds or the timeout is reached.
The action will be retried every .5 seconds until no ExpectFailed
or
FailedCommand
NoSuchElement
exceptions occur. If the timeout is reached,
then a Timeout
exception will be raised. The timeout value
is expressed in seconds.
waitUntil' :: WDSessionStateControl m => Int -> Double -> m a -> m a Source
Similar to waitUntil
but allows you to also specify the poll frequency
of the WD
action. The frequency is expressed as an integer in microseconds.
waitWhile :: WDSessionStateControl m => Double -> m a -> m () Source
Like waitUntil
, but retries the action until it fails or until the timeout
is exceeded.
waitWhile' :: WDSessionStateControl m => Int -> Double -> m a -> m () Source
Like waitUntil'
, but retries the action until it either fails or
until the timeout is exceeded.
Expected conditions
data ExpectFailed Source
An exception representing the failure of an expected condition.
expect :: MonadBaseControl IO m => Bool -> m () Source
An expected condition. This function allows you to express assertions in
your explicit wait. This function raises ExpectFailed
if the given
boolean is False, and otherwise does nothing.
:: MonadBaseControl IO m | |
=> String | Reason why the expected condition failed. |
-> m a |
throws ExpectFailed
. This is nice for writing your own abstractions.
expectAny :: (Foldable f, MonadBaseControl IO m) => (a -> m Bool) -> f a -> m () Source
Apply a monadic predicate to every element in a list, and expect
that
at least one succeeds.
expectAll :: (Foldable f, MonadBaseControl IO m) => (a -> m Bool) -> f a -> m () Source
Apply a monadic predicate to every element in a list, and expect
that all
succeed.
expectNotStale :: WebDriver wd => Element -> wd Element Source
expectAlertOpen :: WebDriver wd => wd Text Source
expect
an alert to be present on the page, and returns its text.
catchFailedCommand :: MonadBaseControl IO m => FailedCommandType -> m a -> m a Source
Catches any FailedCommand
exceptions with the given FailedCommandType
and rethrows as ExpectFailed
Convenience functions
onTimeout :: MonadBaseControl IO m => m a -> m a -> m a Source
Convenience function to catch FailedCommand
Timeout
exceptions
and perform some action.
Example:
waitUntil 5 (getText <=< findElem $ ByCSS ".class") `onTimeout` return ""