hspec-webdriver-0.3.2: 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

        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

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 

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

sessionWith :: TestCapabilities cap => WDConfig -> String -> ([cap], Spec) -> SpecSource

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.

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

Create an example from a WD action. This must be nested inside a call to session or sessionWith.

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 whereSource

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 -> Spec -> (UsingList a, Spec)Source

Multiple sessions at once

multiSessionSource

Arguments

:: (TestCapabilities cap, Typeable a, Eq a) 
=> a

Can be an undefined value of type a, this is used only to determine the type

-> String

the message

-> ([cap], Spec)

the list of capabilites and the spec

-> Spec 

Allows testing multiple browser sessions at once.

The way this works is you create a type a to index the sessions, pass an undefined value to multiSession, and then use values of type a with runWDWith to identify which session the example should run with. The first time runWDWith sees a value, a new session is created. Note that the examples are still run serially in depth-first order.

Note that in hspec1, the requirement that every example inside multiSession must use runWDWith with the same type a is not checked by types. In hspec2 the types are expressive enough so that this can be checked by the type system (and also means multiSession does not need the undefined value of type a).

I use this for testing multiple users at once, with one user in each browser session.

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

usersSession :: TestCapabilities cap => String -> ([cap],Spec) -> Spec
usersSession = multiSession (undefined :: TestUser)

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

spec :: Spec
spec = usersSession "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. 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 runIO to create an IORef while constructing the spec. Note this can be hidden inside the usersSession function.

multiSessionWithSource

Arguments

:: (TestCapabilities cap, Typeable a, Eq a) 
=> WDConfig 
-> a

Can be an undefined value of type a, this is used only to determine the type

-> String

the message

-> ([cap], Spec)

the list of capabilites and the spec

-> Spec 

A variation of multiSession 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.

runWDWith :: (Eq a, Typeable a) => a -> WD () -> WDExample aSource

Create an example from a WD action, parameterized by which session to run. This must be nested inside a call to multiSession or multiSessionWith and can only be used when multiple sessions are running. Also, the type a must match the type given to multiSession.

data WDExample multi Source

An example that can be passed to it containing a webdriver action. It must be created with runWD or runWDWith.

Instances

Typeable multi => Example (WDExample multi) 

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

Methods

newCaps :: c -> IO CapabilitiesSource

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

describe :: String -> Spec -> Spec

Combine a list of specs into a larger spec.

it :: Example a => String -> a -> Spec

Create 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

context :: String -> Spec -> Spec

An alias for describe.

parallel :: Spec -> Spec

Run spec items of given Spec in parallel.

pending :: Expectation

Specifies a pending example.

If you want to textually specify a behavior but do not have an example yet, use this:

 describe "fancyFormatter" $ do
   it "can format text in a way that everyone likes" $
     pending

pendingWith :: String -> Expectation

Specifies a pending example with a reason for why it's pending.

 describe "fancyFormatter" $ do
   it "can format text in a way that everyone likes" $
     pendingWith "waiting for clarification from the designers"

runIO :: IO a -> SpecM a

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

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

Instances

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

Lift a computation from the IO monad.