| Safe Haskell | None |
|---|
Test.Hspec.WebDriver
Contents
Description
Write hspec tests that are webdriver tests, automatically managing the webdriver sessions.
This module re-exports functions from Test.Hspec and Test.WebDriver.Commands and it is
intended that you just import Test.Hspec.WebDriver. If you need to import Test.Hspec or
Test.WebDriver, you should do so using a qualified import.
{-# LANGUAGE OverloadedStrings #-}
module XKCD where
import Test.Hspec.WebDriver
main :: IO ()
main = hspec $
describe "XKCD Tests" $ do
session "for 327" $ using Firefox $ do
it "opens the page" $ runWD $
openPage "http://www.xkcd.com/327/"
it "checks hover text" $ runWD $ do
e <- findElem $ ByCSS "div#comic > img"
e `shouldBeTag` "img"
e `shouldHaveAttr` ("title", "Her daughter is named Help I'm trapped in a driver's license factory.")
parallel $ session "for 303" $ using [Firefox, Chrome] $ do
it "opens the page" $ runWD $
openPage "http://www.xkcd.com/303/"
it "checks the title" $ runWD $ do
e <- findElem $ ById "ctitle"
e `shouldBeTag` "div"
e `shouldHaveText` "Compiling"
The above code assumes selenium-server-standalone is running on 127.0.0.1:4444 at path
/wd/hub (this is the default).
- data BrowserDefaults
- session :: TestCapabilities cap => String -> ([cap], Spec) -> Spec
- sessionOn :: TestCapabilities cap => String -> Word16 -> String -> String -> ([cap], Spec) -> Spec
- runWD :: WD () -> WDExample
- data WDExample
- class Using a where
- shouldBe :: (Show a, Eq a) => a -> a -> WD ()
- shouldBeTag :: Element -> Text -> WD ()
- shouldHaveText :: Element -> Text -> WD ()
- shouldHaveAttr :: Element -> (Text, Text) -> WD ()
- shouldReturn :: (Show a, Eq a) => WD a -> a -> WD ()
- shouldThrow :: (Show e, Eq e, Exception e) => WD a -> e -> WD ()
- class Show c => TestCapabilities c where
- hspec :: Spec -> IO ()
- type Spec = SpecM ()
- describe :: String -> Spec -> Spec
- it :: Example a => String -> a -> Spec
- context :: String -> Spec -> Spec
- parallel :: Spec -> Spec
- pending :: Expectation
- pendingWith :: String -> Expectation
- data WD a
- liftIO :: MonadIO m => forall a. IO a -> m a
Webdriver
data BrowserDefaults Source
Webdriver expectations consist of a set of browser Capabilities to use and the actual test as
a WD monad. The browser capabilities are specified by an enumeration which is an instance of
TestCapabilities. The BrowserDefaults enumeration provides items that represent the default set of
capabilities for each browser (see defaultCaps).
To obtain more control over the capabilities (e.g. to test multiple versions of IE or to test
Firefrox without javascript), you should import Test.Hspec.WebDriver hiding (BrowserDefaults)
and then create your own enumeration which is an instance of TestCapabilities and Using.
session :: TestCapabilities cap => String -> ([cap], Spec) -> SpecSource
Combine the examples nested inside this call into a webdriver session. For each capability in
the list, before the first example is executed, a new webdriver session is created using the
capabilities. The examples are then executed in depth-first order using this webdriver session
(so later examples can rely on the browser state created by earlier examples). Once the final
example has executed, the session is closed. If some WDExample fails (throws an exception),
all remaining examples in the session will become pending.
Note that when using parallel, the examples within a single session will still execute
serially. Different sessions (including the multiple sessions created if more than one
capability is passed to session) will be executed in parallel.
This function uses the default webdriver host (127.0.0.1), port (4444), and
basepath (/wd/hub).
Arguments
| :: TestCapabilities cap | |
| => String | host |
| -> Word16 | port |
| -> String | base path |
| -> String | message |
| -> ([cap], Spec) | |
| -> Spec |
A variation of session which allows you to specify the webdriver host, port, and basepath.
Instances
| Example WDExample |
A typeclass of things which can be converted to a list of capabilities. It's primary purpose
is to allow the word using to be used with session so that the session description reads like
a sentance.
session "for the home page" $ using Firefox $ do
it "loads the page" $ runWD $ do
...
it "scrolls the carosel" $ runWD $ do
...
session "for the users page" $ using [Firefox, Chrome] $ do
...
Instances
Expectations
shouldBeTag :: Element -> Text -> WD ()Source
Asserts that the given element matches the given tag.
shouldHaveText :: Element -> Text -> WD ()Source
Asserts that the given element has the given text.
shouldHaveAttr :: Element -> (Text, Text) -> WD ()Source
Asserts that the given elemnt has the attribute given by (attr name, value).
shouldReturn :: (Show a, Eq a) => WD a -> a -> WD ()Source
Asserts that the action returns the expected result.
shouldThrow :: (Show e, Eq e, Exception e) => WD a -> e -> WD ()Source
Asserts that the action throws an exception.
Custom Capabilities
class Show c => TestCapabilities c whereSource
Provides information about the browser capabilities used for testing. If you want more control
over capabilities, you should hide BrowserDefaults and then make an enumeration of all the
webdriver capabilities you will be testing with. For example,
data TestCaps = Firefox
| FirefoxWithoutJavascript
| Chrome
| IE8
| IE9
deriving (Show, Eq, Bounded, Enum)
TestCaps must then be made an instance of TestCapabilities. Also, instances of Using
should be created.
Instances
Re-exports from Test.Hspec
type Spec = SpecM ()
pending :: Expectation
pendingWith :: String -> Expectation
Re-exports from Test.WebDriver
data WD a