hspec-webdriver-1.0.2: Write end2end web application tests using webdriver and hspec

Safe HaskellNone
LanguageHaskell98

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).

Synopsis

Webdriver Example

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.

Constructors

Firefox 
Chrome 
IE 
Opera 
IPhone 
IPad 
Android 

data WdExample multi Source

A webdriver example.

The webdriver action of type WD () should interact with the webpage using commands from Test.WebDriver.Commands (which is re-exported from this module) and then use the <#g:2 expectations> in this module. It is possible to split up the spec of a single page into multiple examples where later examples start with the web browser state from the end of the previous example. This is helpful to keep each individual example small and allows the entire spec to be described at the beginning with pending examples.

The way this works is that you combine examples into a session using session or sessionWith. A webdriver session is then threaded through all examples in a session so that a later example in the session can rely on the webbrowser state as set up by the previous example. The type system enforces that every webdriver example must be located within a call to session or sessionWith. Indeed, a WdExample produces a SpecWith (WdTestSession multi) which can only be converted to Spec using session or sessionWith. The reason for the WdPending constructor is so that a pending example can be specified with type SpecWith (WdTestSession multi) so it can compose with the other webdriver examples.

The type multi is used when testing multiple sessions at once (e.g. to test multiple interacting users), otherwise it is (). Values of this type are used to determine which browser session the example should be executed against. A new session is created every time a new value of type multi is seen. Note that the type system enforces that every example within the session has the same type multi.

Constructors

WdExample multi (WD ()) 
WdPending (Maybe String) 

Instances

Eq multi => Example (WdExample multi) 
type Arg (WdExample multi) = WdTestSession multi 

runWD :: WD () -> WdExample () Source

A shorthand for constructing a WdExample from a webdriver action when you are only testing a single browser session at once. See the XKCD example at the top of the page.

runWDWith :: multi -> WD () -> WdExample multi Source

Create a webdriver example, specifying which of the multiple sessions the example should be executed against. I suggest you create an enumeration for multi, for example:

data TestUser = Gandolf | Bilbo | Legolas
    deriving (Show, Eq, Enum, Bounded)

runUser :: TestUser -> WD () -> WDExample TestUser
runUser = runWDWith

spec :: Spec
spec = session "tests some page" $ using Firefox $ do
    it "does something with Gandolf" $ runUser Gandolf $ do
        openPage ...
    it "does something with Bilbo" $ runUser Bilbo $ do
        openPage ...
    it "goes back to the Gandolf session" $ runUser Gandolf $ do
        e <- findElem ....
        ...

In the above code, two sessions are created and the examples will go back and forth between the two sessions. Note that a session for Legolas will only be created the first time he shows up in a call to runUser, which might be never. To share information between the sessions (e.g. some data that Gandolf creates that Bilbo should expect), the best way I have found is to use IORefs created with runIO, and then use implicit parameters to pass the IORefs between examples.

pending :: WdExample multi Source

A pending example.

pendingWith :: String -> WdExample multi Source

A pending example with a message.

example :: Default multi => Expectation -> WdExample multi Source

A version of example which lifts an IO () to a webdriver example (so it can be composed with other webdriver examples). In the case of multiple sessions, it doesn't really matter which session the expectation is executed against, so a default value is used. In the case of single sessions, the type is WdExample ().

Webdriver Sessions

session :: TestCapabilities cap => String -> ([cap], SpecWith (WdTestSession multi)) -> Spec Source

Combine the examples nested inside this call into a webdriver session or multiple sessions. For each of the capabilities in the list, the examples are executed one at a time in depth-first order and so later examples can rely on the browser state created by earlier examples. These passes through the examples are independent for different capabilities. Note that when using parallel, the examples within a single pass still execute serially. Different passes through the examples will be executed in parallel. The sessions are managed as follows:

  • In the simplest case when multi is (), before the first example is executed a new webdriver session with the given capabilities is created. The examples are then executed in depth-first order, and the session is then closed when either an exception occurs or the examples complete. (The session can be left open with inspectSession).
  • More generally, as the examples are executed, each time a new value of type multi is seen, a new webdriver session with the capabilities is automatically created. Later examples will continue with the session matching their value of multi.

This function uses the default webdriver host (127.0.0.1), port (4444), and basepath (/wd/hub).

sessionWith :: TestCapabilities cap => WDConfig -> String -> ([cap], SpecWith (WdTestSession multi)) -> Spec Source

A variation of session which allows you to specify the webdriver configuration. Note that the capabilities in the WDConfig will be ignored, instead the capabilities will come from the list of TestCapabilities.

inspectSession :: WD () Source

Abort the session without closing the session.

Normally, session will automatically close the session either when the tests complete without error or when any of the tests within the session throws an error. When developing the test suite, this can be annoying since closing the session causes the browser window to close. Therefore, while developing the test suite, you can insert a call to inspectSession. This will immedietly halt the session (all later tests will fail) but will not close the session so that the browser window stays open.

class Using a where Source

A typeclass of things which can be converted to a list of capabilities. It has two uses. First, it allows you to create a datatype of grouped capabilities in addition to your actual capabilities. These psudo-caps can be passed to using to convert them to a list of your actual capabilities. Secondly, it allows 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
    ...

Associated Types

type UsingList a Source

Methods

using :: a -> SpecWith (WdTestSession multi) -> (UsingList a, SpecWith (WdTestSession multi)) Source

data WdTestSession multi Source

Internal state for webdriver test sessions.

Expectations

shouldBe :: (Show a, Eq a) => a -> a -> WD () Source

shouldBe lifted into the WD monad.

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 where Source

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.

Methods

newCaps :: c -> IO Capabilities Source

The capabilities to pass to createSession.

Re-exports from Test.Hspec

hspec :: Spec -> IO ()

Run given spec and write a report to stdout. Exit with exitFailure if at least one spec item fails.

type Spec = SpecWith ()

type SpecWith a = SpecM a ()

describe :: String -> SpecWith a -> SpecWith a

The describe function combines a list of specs into a larger spec.

context :: String -> SpecWith a -> SpecWith a

context is an alias for describe.

it :: Example a => String -> a -> SpecWith (Arg a)

The it function creates a spec item.

A spec item consists of:

  • a textual description of a desired behavior
  • an example for that behavior
describe "absolute" $ do
  it "returns a positive number when given a negative number" $
    absolute (-1) == 1

specify :: Example a => String -> a -> SpecWith (Arg a)

specify is an alias for it.

parallel :: SpecWith a -> SpecWith a

parallel marks all spec items of the given spec to be safe for parallel evaluation.

runIO :: IO r -> SpecM a r

Run an IO action while constructing the spec tree.

SpecM is a monad to construct a spec tree, without executing any spec items. runIO allows you to run IO actions during this construction phase. The IO action is always run when the spec tree is constructed (e.g. even when --dry-run is specified). If you do not need the result of the IO action to construct the spec tree, beforeAll may be more suitable for your use case.

Re-exports from Test.WebDriver

data WD a :: * -> *

A monadic interface to the WebDriver server. This monad is simply a state monad transformer over IO, threading session information between sequential webdriver commands