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

Safe HaskellNone

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
        it "checks hover text of 327" $ using Firefox $ do
            openPage "http://www.xkcd.com/327/"
            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 $ it "checks title of 303" $ using [Firefox, Chrome] $ do
            openPage "http://www.xkcd.com/303/"
            e <- findElem $ ById "ctitle"
            e `shouldBeTag` "div"
            e `shouldHaveText` "Compiling"

        it "checks image of 1310" pending

The above code assumes selenium-server-standalone is running on 127.0.0.1:4444 at path /wd/hub (this is the default). You can configure this using createSessionManager'.

Synopsis

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. When creating new sessions, the defaultCaps are used. Also, any existing session (which exists at program startup) which matches the browser is used, no matter the actual capabilities.

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 

it :: (Show cap, TestCapabilities cap) => String -> WdExpectation cap -> SpecSource

Create a spec from a webdriver expectation.

The webdriver expectation consists of a list of browser capabilities and the actual test. The test will be executed once for each set of capabilities in the list. By default, the tests will be executed serially. You can use parallel to execute the test on all capabilities in parallel.

To run the test, a webdriver session is allocated from a pool of sessions (in a thread-safe manner). The pools will be initialized automatically from existing sessions the first time a test is run; you can explicitly create the pools using createSessionManager.

class Using a whereSource

A typeclass of things which can be converted to a WdExpectation. This is the primary method to create expectations to pass to it. Both a single BrowserDefaults and a list of BrowserDefaults can be used.

it "opens the home page" $ using Firefox $ do
    ...
it "opens the users page" $ using [Firefox, Chrome] $ do
    ...

Associated Types

type UsingCapabilities a :: *Source

pending :: WdExpectation ()Source

A WdExpectation that is pending.

pendingWith :: String -> WdExpectation ()Source

A WdExpectation that is pending, with a message.

data WdExpectation cap Source

A webdriver expectation is either an action and a list of capabilities (which should be an instance of TestCapabilities) or a pending message.

Constructors

WdTest [cap] (WD ()) 
WdPending (Maybe String) 

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.

Session Manager

createSessionManagerSource

Arguments

:: Int

threshold number of sessions per enumeration item beyond which new sessions are no longer created. Note you can set this to zero so that new sessions are never created; the only sessions used will be those that already exist.

-> IO () 

Create a new session manager using the default webdriver host (127.0.0.1), port (4444), and basepath (/wd/hub).

The session manager hands out sessions to tests (in a thread-safe manner). Threads ask for sessions by an enumeration which is an instance of TestCapabilities, and the manager stores a pool of sessions for each enumeration item. When calling createSessionManager, the already existing sessions are loaded and used as the initial sessions in the pools. If a thread asks for a session but none is available, one of two things happens: if the total number of sessions for this enumeration item is larger than the argument to createSessionManager, the thread will block until a session is available. If the total number of sessions for this enumeration item is smaller, a new session will be created. This is only relevant if you run tests in parallel, since when running tests serially at most one session will be in use at any one time in any case. Note that sessions are never closed by the manager.

If you do not call createSessionManager, when the very first test is run a new manager will be created where the maximum number of sessions per enumeration item is one.

createSessionManager'Source

Arguments

:: Int

threshold number of sessions per enumeration item

-> String

host

-> Word16

port

-> String

base path

-> IO () 

Same as createSessionManager but allows you to specify the webdriver host, port, and base path for all sessions.

Custom Capabilities

class (Eq c, Enum c, Typeable 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, Typeable)

TestCaps must then be made an instance of TestCapabilities. Also, instances of Using should be created.

Methods

matchesCaps :: c -> Capabilities -> BoolSource

Check if the Capabilities match your enumeration. Note that these capabilities will be the actual capabilities (with things like version information filled in) so you should not use == to compare capabilities, only check the actual capabilities you care about.

newCaps :: c -> WD CapabilitiesSource

The capabilities to pass to createSession when no existing session is found.

Instances

TestCapabilities ()

This instance is used for pending messages, no capabilities are matched or created.

TestCapabilities BrowserDefaults 

Re-exports from 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 = SpecM ()

describe :: String -> Spec -> Spec

Combine a list of specs into a larger spec.

context :: String -> Spec -> Spec

An alias for describe.

parallel :: Spec -> Spec

Run examples of given spec in parallel.

Future TODO: lift before, after, and around into the WD monad.

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

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

Internal

withCaps :: TestCapabilities s => s -> WD a -> WD aSource

Find or create a new session, set it into the WD monad, run the given action, and return the session back into the pool once the action completes or an exception occurs.