{-# LANGUAGE OverloadedStrings, FlexibleInstances, DeriveDataTypeable, TypeFamilies, CPP, NamedFieldPuns #-}
module Test.Hspec.WebDriver(
WdExample(..)
, WdOptions (..)
, runWD
, runWDOptions
, runWDWith
, runWDWithOptions
, pending
, pendingWith
, example
, session
, sessionWith
, inspectSession
, using
, WdTestSession
, firefoxCaps
, chromeCaps
, ieCaps
, operaCaps
, iphoneCaps
, ipadCaps
, androidCaps
, shouldBe
, shouldBeTag
, shouldHaveText
, shouldHaveAttr
, shouldReturn
, shouldThrow
, hspec
, Spec
, SpecWith
, describe
, context
, it
, specify
, parallel
, runIO
, WD
, Capabilities
, module Test.WebDriver.Commands
) where
import Control.Concurrent.MVar (MVar, takeMVar, putMVar, newEmptyMVar)
import Control.Exception (SomeException(..))
import Control.Exception.Lifted (try, Exception, onException, throwIO)
import Control.Monad (replicateM)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.State (state, evalState, execState)
import Data.Default (Default(..))
import Data.IORef (newIORef, writeIORef, readIORef)
import qualified Data.Text as T
import Data.Typeable (Typeable, cast)
import Test.HUnit (assertEqual, assertFailure)
import qualified Data.Aeson as A
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>), Applicative)
import Data.Traversable (traverse)
#endif
import qualified Test.Hspec as H
import Test.Hspec hiding (shouldReturn, shouldBe, shouldSatisfy, shouldThrow, pending, pendingWith, example)
import Test.Hspec.Core.Spec (Result(..), ResultStatus(..))
import Test.Hspec.Core.Spec (Item(..), Example(..), SpecTree, Tree(..), fromSpecList, runSpecM)
import Test.WebDriver (WD, Capabilities)
import qualified Test.WebDriver as W
import Test.WebDriver.Commands
import qualified Test.WebDriver.Config as W
import qualified Test.WebDriver.Capabilities as W
import qualified Test.WebDriver.Session as W
data SessionState multi = SessionState {
forall multi. SessionState multi -> [(multi, WDSession)]
stSessionMap :: [(multi, W.WDSession)]
, forall multi. SessionState multi -> Bool
stPrevHadError :: Bool
, forall multi. SessionState multi -> Bool
stPrevAborted :: Bool
, forall multi. SessionState multi -> IO WDSession
stCreateSession :: IO W.WDSession
}
data WdTestSession multi = WdTestSession {
forall multi. WdTestSession multi -> IO (SessionState multi)
wdTestOpen :: IO (SessionState multi)
, forall multi. WdTestSession multi -> SessionState multi -> IO ()
wdTestClose :: SessionState multi -> IO ()
}
data WdExample multi = WdExample multi WdOptions (WD ()) | WdPending (Maybe String)
data WdOptions = WdOptions {
WdOptions -> Bool
skipRemainingTestsAfterFailure :: Bool
}
instance Default WdOptions where
def :: WdOptions
def = WdOptions { skipRemainingTestsAfterFailure :: Bool
skipRemainingTestsAfterFailure = Bool
True }
runWD :: WD () -> WdExample ()
runWD :: WD () -> WdExample ()
runWD = () -> WdOptions -> WD () -> WdExample ()
forall multi. multi -> WdOptions -> WD () -> WdExample multi
WdExample () WdOptions
forall a. Default a => a
def
runWDOptions :: WdOptions -> WD () -> WdExample ()
runWDOptions :: WdOptions -> WD () -> WdExample ()
runWDOptions = () -> WdOptions -> WD () -> WdExample ()
forall multi. multi -> WdOptions -> WD () -> WdExample multi
WdExample ()
runWDWith :: multi -> WD () -> WdExample multi
runWDWith :: forall multi. multi -> WD () -> WdExample multi
runWDWith multi
multi = multi -> WdOptions -> WD () -> WdExample multi
forall multi. multi -> WdOptions -> WD () -> WdExample multi
WdExample multi
multi WdOptions
forall a. Default a => a
def
runWDWithOptions :: multi -> WdOptions -> WD () -> WdExample multi
runWDWithOptions :: forall multi. multi -> WdOptions -> WD () -> WdExample multi
runWDWithOptions = multi -> WdOptions -> WD () -> WdExample multi
forall multi. multi -> WdOptions -> WD () -> WdExample multi
WdExample
pending :: WdExample multi
pending :: forall multi. WdExample multi
pending = Maybe [Char] -> WdExample multi
forall multi. Maybe [Char] -> WdExample multi
WdPending Maybe [Char]
forall a. Maybe a
Nothing
pendingWith :: String -> WdExample multi
pendingWith :: forall multi. [Char] -> WdExample multi
pendingWith = Maybe [Char] -> WdExample multi
forall multi. Maybe [Char] -> WdExample multi
WdPending (Maybe [Char] -> WdExample multi)
-> ([Char] -> Maybe [Char]) -> [Char] -> WdExample multi
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just
example :: Default multi => Expectation -> WdExample multi
example :: forall multi. Default multi => IO () -> WdExample multi
example = multi -> WdOptions -> WD () -> WdExample multi
forall multi. multi -> WdOptions -> WD () -> WdExample multi
WdExample multi
forall a. Default a => a
def WdOptions
forall a. Default a => a
def (WD () -> WdExample multi)
-> (IO () -> WD ()) -> IO () -> WdExample multi
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
session :: String -> ([Capabilities], SpecWith (WdTestSession multi)) -> Spec
session :: forall multi.
[Char] -> ([Capabilities], SpecWith (WdTestSession multi)) -> Spec
session [Char]
msg ([Capabilities]
caps, SpecWith (WdTestSession multi)
spec) = WDConfig
-> [Char]
-> ([(Capabilities, [Char])], SpecWith (WdTestSession multi))
-> Spec
forall multi.
WDConfig
-> [Char]
-> ([(Capabilities, [Char])], SpecWith (WdTestSession multi))
-> Spec
sessionWith WDConfig
W.defaultConfig [Char]
msg ([(Capabilities, [Char])]
caps', SpecWith (WdTestSession multi)
spec)
where
caps' :: [(Capabilities, [Char])]
caps' = (Capabilities -> (Capabilities, [Char]))
-> [Capabilities] -> [(Capabilities, [Char])]
forall a b. (a -> b) -> [a] -> [b]
map Capabilities -> (Capabilities, [Char])
f [Capabilities]
caps
f :: Capabilities -> (Capabilities, [Char])
f Capabilities
c = case Browser -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Capabilities -> Browser
W.browser Capabilities
c) of
A.String Text
b -> (Capabilities
c, Text -> [Char]
T.unpack Text
b)
Value
_ -> (Capabilities
c, Capabilities -> [Char]
forall a. Show a => a -> [Char]
show Capabilities
c)
sessionWith :: W.WDConfig -> String -> ([(Capabilities, String)], SpecWith (WdTestSession multi)) -> Spec
sessionWith :: forall multi.
WDConfig
-> [Char]
-> ([(Capabilities, [Char])], SpecWith (WdTestSession multi))
-> Spec
sessionWith WDConfig
cfg [Char]
msg ([(Capabilities, [Char])]
caps, SpecWith (WdTestSession multi)
spec) = Spec
SpecWith (Arg (IO ()))
spec'
where
procT :: Capabilities -> Spec
procT Capabilities
c = WDConfig -> Capabilities -> SpecWith (WdTestSession multi) -> Spec
forall multi.
WDConfig -> Capabilities -> SpecWith (WdTestSession multi) -> Spec
procTestSession WDConfig
cfg (Capabilities -> Capabilities
forall t. GetCapabilities t => t -> Capabilities
W.getCaps Capabilities
c) SpecWith (WdTestSession multi)
spec
spec' :: SpecWith (Arg (IO ()))
spec' = case [(Capabilities, [Char])]
caps of
[] -> [Char] -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
[Char] -> a -> SpecWith (Arg a)
it [Char]
msg (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ HasCallStack => [Char] -> IO ()
[Char] -> IO ()
H.pendingWith [Char]
"No capabilities specified"
[(Capabilities
c,[Char]
cDscr)] -> [Char] -> Spec -> Spec
forall a. HasCallStack => [Char] -> SpecWith a -> SpecWith a
describe ([Char]
msg [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" using " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
cDscr) (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ Capabilities -> Spec
procT Capabilities
c
[(Capabilities, [Char])]
_ -> [Char] -> Spec -> Spec
forall a. HasCallStack => [Char] -> SpecWith a -> SpecWith a
describe [Char]
msg (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ ((Capabilities, [Char]) -> Spec)
-> [(Capabilities, [Char])] -> Spec
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Capabilities
c,[Char]
cDscr) -> [Char] -> Spec -> Spec
forall a. HasCallStack => [Char] -> SpecWith a -> SpecWith a
describe ([Char]
"using " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
cDscr) (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ Capabilities -> Spec
procT Capabilities
c) [(Capabilities, [Char])]
caps
using :: [caps] -> SpecWith (WdTestSession multi) -> ([caps], SpecWith (WdTestSession multi))
using :: forall caps multi.
[caps]
-> SpecWith (WdTestSession multi)
-> ([caps], SpecWith (WdTestSession multi))
using = (,)
firefoxCaps, chromeCaps, ieCaps, operaCaps, iphoneCaps, ipadCaps, androidCaps :: Capabilities
firefoxCaps :: Capabilities
firefoxCaps = Capabilities
W.defaultCaps { W.browser = W.firefox }
chromeCaps :: Capabilities
chromeCaps = Capabilities
W.defaultCaps { W.browser = W.chrome }
ieCaps :: Capabilities
ieCaps = Capabilities
W.defaultCaps { W.browser = W.ie }
operaCaps :: Capabilities
operaCaps = Capabilities
W.defaultCaps { W.browser = W.opera }
iphoneCaps :: Capabilities
iphoneCaps = Capabilities
W.defaultCaps { W.browser = W.iPhone }
ipadCaps :: Capabilities
ipadCaps = Capabilities
W.defaultCaps { W.browser = W.iPad }
androidCaps :: Capabilities
androidCaps = Capabilities
W.defaultCaps { W.browser = W.android }
data AbortSession = AbortSession
deriving (Int -> AbortSession -> [Char] -> [Char]
[AbortSession] -> [Char] -> [Char]
AbortSession -> [Char]
(Int -> AbortSession -> [Char] -> [Char])
-> (AbortSession -> [Char])
-> ([AbortSession] -> [Char] -> [Char])
-> Show AbortSession
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> AbortSession -> [Char] -> [Char]
showsPrec :: Int -> AbortSession -> [Char] -> [Char]
$cshow :: AbortSession -> [Char]
show :: AbortSession -> [Char]
$cshowList :: [AbortSession] -> [Char] -> [Char]
showList :: [AbortSession] -> [Char] -> [Char]
Show, Typeable)
instance Exception AbortSession
inspectSession :: WD ()
inspectSession :: WD ()
inspectSession = AbortSession -> WD ()
forall (m :: * -> *) e a. (MonadBase IO m, Exception e) => e -> m a
throwIO AbortSession
AbortSession
shouldBe :: (Show a, Eq a) => a -> a -> WD ()
a
x shouldBe :: forall a. (Show a, Eq a) => a -> a -> WD ()
`shouldBe` a
y = IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ a
x a -> a -> IO ()
forall a. (HasCallStack, Show a, Eq a) => a -> a -> IO ()
`H.shouldBe` a
y
shouldBeTag :: Element -> T.Text -> WD ()
Element
e shouldBeTag :: Element -> Text -> WD ()
`shouldBeTag` Text
name = do
Text
t <- Element -> WD Text
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Text
tagName Element
e
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ [Char] -> Text -> Text -> IO ()
forall a. (HasCallStack, Eq a, Show a) => [Char] -> a -> a -> IO ()
assertEqual ([Char]
"tag of " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Element -> [Char]
forall a. Show a => a -> [Char]
show Element
e) Text
name Text
t
shouldHaveText :: Element -> T.Text -> WD ()
Element
e shouldHaveText :: Element -> Text -> WD ()
`shouldHaveText` Text
txt = do
Text
t <- Element -> WD Text
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> wd Text
getText Element
e
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ [Char] -> Text -> Text -> IO ()
forall a. (HasCallStack, Eq a, Show a) => [Char] -> a -> a -> IO ()
assertEqual ([Char]
"text of " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Element -> [Char]
forall a. Show a => a -> [Char]
show Element
e) Text
txt Text
t
shouldHaveAttr :: Element -> (T.Text, T.Text) -> WD ()
Element
e shouldHaveAttr :: Element -> (Text, Text) -> WD ()
`shouldHaveAttr` (Text
a, Text
txt) = do
Maybe Text
t <- Element -> Text -> WD (Maybe Text)
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Element -> Text -> wd (Maybe Text)
attr Element
e Text
a
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ [Char] -> Maybe Text -> Maybe Text -> IO ()
forall a. (HasCallStack, Eq a, Show a) => [Char] -> a -> a -> IO ()
assertEqual ([Char]
"attribute " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
T.unpack Text
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" of " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Element -> [Char]
forall a. Show a => a -> [Char]
show Element
e) (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
txt) Maybe Text
t
shouldReturn :: (Show a, Eq a) => WD a -> a -> WD ()
WD a
action shouldReturn :: forall a. (Show a, Eq a) => WD a -> a -> WD ()
`shouldReturn` a
expected = WD a
action WD a -> (a -> WD ()) -> WD ()
forall a b. WD a -> (a -> WD b) -> WD b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\a
a -> IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ a
a a -> a -> IO ()
forall a. (HasCallStack, Show a, Eq a) => a -> a -> IO ()
`H.shouldBe` a
expected)
shouldThrow :: (Show e, Eq e, Exception e) => WD a -> e -> WD ()
shouldThrow :: forall e a. (Show e, Eq e, Exception e) => WD a -> e -> WD ()
shouldThrow WD a
w e
expected = do
Either e a
r <- WD a -> WD (Either e a)
forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> m (Either e a)
try WD a
w
case Either e a
r of
Left e
err -> e
err e -> e -> WD ()
forall a. (Show a, Eq a) => a -> a -> WD ()
`shouldBe` e
expected
Right a
_ -> IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ [Char] -> IO ()
forall a. HasCallStack => [Char] -> IO a
assertFailure ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"did not get expected exception " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ e -> [Char]
forall a. Show a => a -> [Char]
show e
expected
createTestSession :: W.WDConfig -> [MVar (SessionState multi)] -> Int -> WdTestSession multi
createTestSession :: forall multi.
WDConfig
-> [MVar (SessionState multi)] -> Int -> WdTestSession multi
createTestSession WDConfig
cfg [MVar (SessionState multi)]
mvars Int
n = IO (SessionState multi)
-> (SessionState multi -> IO ()) -> WdTestSession multi
forall multi.
IO (SessionState multi)
-> (SessionState multi -> IO ()) -> WdTestSession multi
WdTestSession IO (SessionState multi)
open SessionState multi -> IO ()
close
where
open :: IO (SessionState multi)
open | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = SessionState multi -> IO (SessionState multi)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SessionState multi -> IO (SessionState multi))
-> SessionState multi -> IO (SessionState multi)
forall a b. (a -> b) -> a -> b
$ [(multi, WDSession)]
-> Bool -> Bool -> IO WDSession -> SessionState multi
forall multi.
[(multi, WDSession)]
-> Bool -> Bool -> IO WDSession -> SessionState multi
SessionState [] Bool
False Bool
False IO WDSession
create
| Bool
otherwise = MVar (SessionState multi) -> IO (SessionState multi)
forall a. MVar a -> IO a
takeMVar ([MVar (SessionState multi)]
mvars [MVar (SessionState multi)] -> Int -> MVar (SessionState multi)
forall a. HasCallStack => [a] -> Int -> a
!! Int
n)
create :: IO WDSession
create = do
WDSession
s <- WDConfig -> IO WDSession
forall c (m :: * -> *).
(WebDriverConfig c, MonadBase IO m) =>
c -> m WDSession
forall (m :: * -> *). MonadBase IO m => WDConfig -> m WDSession
W.mkSession WDConfig
cfg
#if MIN_VERSION_webdriver(0,7,0)
WDSession -> WD WDSession -> IO WDSession
forall a. WDSession -> WD a -> IO a
W.runWD WDSession
s (WD WDSession -> IO WDSession) -> WD WDSession -> IO WDSession
forall a b. (a -> b) -> a -> b
$ Capabilities -> WD WDSession
forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Capabilities -> wd WDSession
createSession (Capabilities -> WD WDSession) -> Capabilities -> WD WDSession
forall a b. (a -> b) -> a -> b
$ WDConfig -> Capabilities
W.wdCapabilities WDConfig
cfg
#else
W.runWD s $ createSession [] $ W.wdCapabilities cfg
#endif
close :: SessionState multi -> IO ()
close SessionState multi
st | [MVar (SessionState multi)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [MVar (SessionState multi)]
mvars Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n = ((multi, WDSession) -> IO ()) -> [(multi, WDSession)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((WDSession -> WD () -> IO ()
forall a. WDSession -> WD a -> IO a
`W.runWD` WD ()
forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
closeSession) (WDSession -> IO ())
-> ((multi, WDSession) -> WDSession) -> (multi, WDSession) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (multi, WDSession) -> WDSession
forall a b. (a, b) -> b
snd) ([(multi, WDSession)] -> IO ()) -> [(multi, WDSession)] -> IO ()
forall a b. (a -> b) -> a -> b
$ SessionState multi -> [(multi, WDSession)]
forall multi. SessionState multi -> [(multi, WDSession)]
stSessionMap SessionState multi
st
| Bool
otherwise = MVar (SessionState multi) -> SessionState multi -> IO ()
forall a. MVar a -> a -> IO ()
putMVar ([MVar (SessionState multi)]
mvars [MVar (SessionState multi)] -> Int -> MVar (SessionState multi)
forall a. HasCallStack => [a] -> Int -> a
!! (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) SessionState multi
st
procSpecItem :: W.WDConfig -> [MVar (SessionState multi)] -> Int -> Item (WdTestSession multi) -> Item ()
procSpecItem :: forall multi.
WDConfig
-> [MVar (SessionState multi)]
-> Int
-> Item (WdTestSession multi)
-> Item ()
procSpecItem WDConfig
cfg [MVar (SessionState multi)]
mvars Int
n Item (WdTestSession multi)
item = Item (WdTestSession multi)
item { itemExample = \Params
p ActionWith () -> IO ()
act ProgressCallback
progress -> Item (WdTestSession multi)
-> Params
-> (ActionWith (WdTestSession multi) -> IO ())
-> ProgressCallback
-> IO Result
forall a.
Item a
-> Params
-> (ActionWith a -> IO ())
-> ProgressCallback
-> IO Result
itemExample Item (WdTestSession multi)
item Params
p (ActionWith () -> IO ()
act (ActionWith () -> IO ())
-> (ActionWith (WdTestSession multi) -> ActionWith ())
-> ActionWith (WdTestSession multi)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionWith (WdTestSession multi) -> ActionWith ()
act') ProgressCallback
progress }
where
act' :: ActionWith (WdTestSession multi) -> ActionWith ()
act' ActionWith (WdTestSession multi)
f () = ActionWith (WdTestSession multi)
f (WDConfig
-> [MVar (SessionState multi)] -> Int -> WdTestSession multi
forall multi.
WDConfig
-> [MVar (SessionState multi)] -> Int -> WdTestSession multi
createTestSession WDConfig
cfg [MVar (SessionState multi)]
mvars Int
n)
procTestSession :: W.WDConfig -> Capabilities -> SpecWith (WdTestSession multi) -> Spec
procTestSession :: forall multi.
WDConfig -> Capabilities -> SpecWith (WdTestSession multi) -> Spec
procTestSession WDConfig
cfg Capabilities
cap SpecWith (WdTestSession multi)
s = do
([MVar (SessionState multi)]
mvars, [SpecTree (WdTestSession multi)]
trees) <- IO ([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
-> SpecM
() ([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
forall r a. IO r -> SpecM a r
runIO (IO ([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
-> SpecM
() ([MVar (SessionState multi)], [SpecTree (WdTestSession multi)]))
-> IO
([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
-> SpecM
() ([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
forall a b. (a -> b) -> a -> b
$ do
#if MIN_VERSION_hspec_core(2,10,0)
(Endo Config
_, [SpecTree (WdTestSession multi)]
trees) <- SpecWith (WdTestSession multi)
-> IO (Endo Config, [SpecTree (WdTestSession multi)])
forall a. SpecWith a -> IO (Endo Config, [SpecTree a])
runSpecM SpecWith (WdTestSession multi)
s
#else
trees <- runSpecM s
#endif
let cnt :: Int
cnt = [SpecTree (WdTestSession multi)] -> Int
forall a. [SpecTree a] -> Int
countItems [SpecTree (WdTestSession multi)]
trees
[MVar (SessionState multi)]
mvars <- Int
-> IO (MVar (SessionState multi)) -> IO [MVar (SessionState multi)]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
cnt IO (MVar (SessionState multi))
forall a. IO (MVar a)
newEmptyMVar
([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
-> IO
([MVar (SessionState multi)], [SpecTree (WdTestSession multi)])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([MVar (SessionState multi)]
mvars, [SpecTree (WdTestSession multi)]
trees)
[SpecTree ()] -> Spec
forall a. [SpecTree a] -> SpecWith a
fromSpecList ([SpecTree ()] -> Spec) -> [SpecTree ()] -> Spec
forall a b. (a -> b) -> a -> b
$ (Int -> Item (WdTestSession multi) -> Item ())
-> [SpecTree (WdTestSession multi)] -> [SpecTree ()]
forall a b.
(Int -> Item a -> Item b) -> [SpecTree a] -> [SpecTree b]
mapWithCounter (WDConfig
-> [MVar (SessionState multi)]
-> Int
-> Item (WdTestSession multi)
-> Item ()
forall multi.
WDConfig
-> [MVar (SessionState multi)]
-> Int
-> Item (WdTestSession multi)
-> Item ()
procSpecItem WDConfig
cfg {W.wdCapabilities = cap} [MVar (SessionState multi)]
mvars) [SpecTree (WdTestSession multi)]
trees
instance Eq multi => Example (WdExample multi) where
type Arg (WdExample multi) = WdTestSession multi
evaluateExample :: WdExample multi
-> Params
-> (ActionWith (Arg (WdExample multi)) -> IO ())
-> ProgressCallback
-> IO Result
evaluateExample (WdPending Maybe [Char]
msg) Params
_ ActionWith (Arg (WdExample multi)) -> IO ()
_ ProgressCallback
_ = Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ [Char] -> ResultStatus -> Result
Result [Char]
"" (Maybe Location -> Maybe [Char] -> ResultStatus
Pending Maybe Location
forall a. Maybe a
Nothing Maybe [Char]
msg)
evaluateExample (WdExample multi
multi (WdOptions {Bool
skipRemainingTestsAfterFailure :: WdOptions -> Bool
skipRemainingTestsAfterFailure :: Bool
skipRemainingTestsAfterFailure}) WD ()
wd) Params
_ ActionWith (Arg (WdExample multi)) -> IO ()
act ProgressCallback
_ = do
IORef Bool
prevHadError <- Bool -> IO (IORef Bool)
forall a. a -> IO (IORef a)
newIORef Bool
False
IORef Bool
aborted <- Bool -> IO (IORef Bool)
forall a. a -> IO (IORef a)
newIORef Bool
False
ActionWith (Arg (WdExample multi)) -> IO ()
act (ActionWith (Arg (WdExample multi)) -> IO ())
-> ActionWith (Arg (WdExample multi)) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Arg (WdExample multi)
testsession -> do
SessionState multi
tstate <- WdTestSession multi -> IO (SessionState multi)
forall multi. WdTestSession multi -> IO (SessionState multi)
wdTestOpen Arg (WdExample multi)
WdTestSession multi
testsession
Maybe WDSession
msess <- case (multi -> [(multi, WDSession)] -> Maybe WDSession
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup multi
multi ([(multi, WDSession)] -> Maybe WDSession)
-> [(multi, WDSession)] -> Maybe WDSession
forall a b. (a -> b) -> a -> b
$ SessionState multi -> [(multi, WDSession)]
forall multi. SessionState multi -> [(multi, WDSession)]
stSessionMap SessionState multi
tstate,
(SessionState multi -> Bool
forall multi. SessionState multi -> Bool
stPrevHadError SessionState multi
tstate Bool -> Bool -> Bool
|| SessionState multi -> Bool
forall multi. SessionState multi -> Bool
stPrevAborted SessionState multi
tstate) Bool -> Bool -> Bool
&& Bool
skipRemainingTestsAfterFailure) of
(Maybe WDSession
_, Bool
True) -> Maybe WDSession -> IO (Maybe WDSession)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe WDSession
forall a. Maybe a
Nothing
(Just WDSession
s, Bool
False) -> Maybe WDSession -> IO (Maybe WDSession)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe WDSession -> IO (Maybe WDSession))
-> Maybe WDSession -> IO (Maybe WDSession)
forall a b. (a -> b) -> a -> b
$ WDSession -> Maybe WDSession
forall a. a -> Maybe a
Just WDSession
s
(Maybe WDSession
Nothing, Bool
False) ->
WDSession -> Maybe WDSession
forall a. a -> Maybe a
Just (WDSession -> Maybe WDSession)
-> IO WDSession -> IO (Maybe WDSession)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SessionState multi -> IO WDSession
forall multi. SessionState multi -> IO WDSession
stCreateSession SessionState multi
tstate
IO WDSession -> IO () -> IO WDSession
forall (m :: * -> *) a b.
MonadBaseControl IO m =>
m a -> m b -> m a
`onException` WdTestSession multi -> SessionState multi -> IO ()
forall multi. WdTestSession multi -> SessionState multi -> IO ()
wdTestClose Arg (WdExample multi)
WdTestSession multi
testsession SessionState multi
tstate { stPrevHadError = True }
case Maybe WDSession
msess of
Just WDSession
wdsession -> WDSession -> WD () -> IO ()
forall a. WDSession -> WD a -> IO a
W.runWD WDSession
wdsession (WD () -> IO ()) -> WD () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Either SomeException ()
macterr <- WD () -> WD (Either SomeException ())
forall (m :: * -> *) e a.
(MonadBaseControl IO m, Exception e) =>
m a -> m (Either e a)
try WD ()
wd
case Either SomeException ()
macterr of
Right () -> do
WDSession
wdsession' <- WD WDSession
forall (m :: * -> *). WDSessionState m => m WDSession
W.getSession
let smap :: [(multi, WDSession)]
smap = (multi
multi, WDSession
wdsession') (multi, WDSession) -> [(multi, WDSession)] -> [(multi, WDSession)]
forall a. a -> [a] -> [a]
: ((multi, WDSession) -> Bool)
-> [(multi, WDSession)] -> [(multi, WDSession)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((multi -> multi -> Bool
forall a. Eq a => a -> a -> Bool
/=multi
multi) (multi -> Bool)
-> ((multi, WDSession) -> multi) -> (multi, WDSession) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (multi, WDSession) -> multi
forall a b. (a, b) -> a
fst) (SessionState multi -> [(multi, WDSession)]
forall multi. SessionState multi -> [(multi, WDSession)]
stSessionMap SessionState multi
tstate)
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ WdTestSession multi -> SessionState multi -> IO ()
forall multi. WdTestSession multi -> SessionState multi -> IO ()
wdTestClose Arg (WdExample multi)
WdTestSession multi
testsession SessionState multi
tstate { stSessionMap = smap }
Left acterr :: SomeException
acterr@(SomeException e
actex) ->
case e -> Maybe AbortSession
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
actex of
Just AbortSession
AbortSession -> do
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ WdTestSession multi -> SessionState multi -> IO ()
forall multi. WdTestSession multi -> SessionState multi -> IO ()
wdTestClose Arg (WdExample multi)
WdTestSession multi
testsession SessionState multi
tstate { stSessionMap = [], stPrevAborted = True }
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
aborted Bool
True
Maybe AbortSession
Nothing -> do
IO () -> WD ()
forall a. IO a -> WD a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> WD ()) -> IO () -> WD ()
forall a b. (a -> b) -> a -> b
$ WdTestSession multi -> SessionState multi -> IO ()
forall multi. WdTestSession multi -> SessionState multi -> IO ()
wdTestClose Arg (WdExample multi)
WdTestSession multi
testsession SessionState multi
tstate { stPrevHadError = True }
SomeException -> WD ()
forall (m :: * -> *) e a. (MonadBase IO m, Exception e) => e -> m a
throwIO SomeException
acterr
Maybe WDSession
_ -> do
IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
prevHadError (Bool -> IO ()) -> Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ SessionState multi -> Bool
forall multi. SessionState multi -> Bool
stPrevHadError SessionState multi
tstate
IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
aborted (Bool -> IO ()) -> Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ SessionState multi -> Bool
forall multi. SessionState multi -> Bool
stPrevAborted SessionState multi
tstate
WdTestSession multi -> SessionState multi -> IO ()
forall multi. WdTestSession multi -> SessionState multi -> IO ()
wdTestClose Arg (WdExample multi)
WdTestSession multi
testsession SessionState multi
tstate
Bool
merr <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
prevHadError
Bool
mabort <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
aborted
Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ case (Bool
merr, Bool
mabort) of
(Bool
True, Bool
_) -> [Char] -> ResultStatus -> Result
Result [Char]
"" (Maybe Location -> Maybe [Char] -> ResultStatus
Pending Maybe Location
forall a. Maybe a
Nothing ([Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
"Previous example had an error"))
(Bool
_, Bool
True) -> [Char] -> ResultStatus -> Result
Result [Char]
"" (Maybe Location -> Maybe [Char] -> ResultStatus
Pending Maybe Location
forall a. Maybe a
Nothing ([Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
"Session has been aborted"))
(Bool, Bool)
_ -> [Char] -> ResultStatus -> Result
Result [Char]
"" ResultStatus
Success
#if MIN_VERSION_hspec_core(2,10,0)
traverseSpec :: Applicative f => (Item a -> f (Item b)) -> [SpecTree a] -> f [SpecTree b]
traverseSpec :: forall (f :: * -> *) a b.
Applicative f =>
(Item a -> f (Item b)) -> [SpecTree a] -> f [SpecTree b]
traverseSpec = (SpecTree a -> f (SpecTree b)) -> [SpecTree a] -> f [SpecTree b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((SpecTree a -> f (SpecTree b)) -> [SpecTree a] -> f [SpecTree b])
-> ((Item a -> f (Item b)) -> SpecTree a -> f (SpecTree b))
-> (Item a -> f (Item b))
-> [SpecTree a]
-> f [SpecTree b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Item a -> f (Item b)) -> SpecTree a -> f (SpecTree b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Tree (IO ()) a -> f (Tree (IO ()) b)
traverse
#else
traverseTree :: Applicative f => (Item a -> f (Item b)) -> SpecTree a -> f (SpecTree b)
traverseTree f (Leaf i) = Leaf <$> f i
traverseTree f (Node msg ss) = Node msg <$> traverse (traverseTree f) ss
#if MIN_VERSION_hspec_core(2,8,0)
traverseTree f (NodeWithCleanup loc c ss) = NodeWithCleanup loc c' <$> traverse (traverseTree f) ss
#else
traverseTree f (NodeWithCleanup c ss) = NodeWithCleanup c' <$> traverse (traverseTree f) ss
#endif
where
c' _b = c undefined
traverseSpec :: Applicative f => (Item a -> f (Item b)) -> [SpecTree a] -> f [SpecTree b]
traverseSpec f = traverse (traverseTree f)
#endif
mapWithCounter :: (Int -> Item a -> Item b) -> [SpecTree a] -> [SpecTree b]
mapWithCounter :: forall a b.
(Int -> Item a -> Item b) -> [SpecTree a] -> [SpecTree b]
mapWithCounter Int -> Item a -> Item b
f [SpecTree a]
s = (State Int [SpecTree b] -> Int -> [SpecTree b])
-> Int -> State Int [SpecTree b] -> [SpecTree b]
forall a b c. (a -> b -> c) -> b -> a -> c
flip State Int [SpecTree b] -> Int -> [SpecTree b]
forall s a. State s a -> s -> a
evalState Int
0 (State Int [SpecTree b] -> [SpecTree b])
-> State Int [SpecTree b] -> [SpecTree b]
forall a b. (a -> b) -> a -> b
$ (Item a -> StateT Int Identity (Item b))
-> [SpecTree a] -> State Int [SpecTree b]
forall (f :: * -> *) a b.
Applicative f =>
(Item a -> f (Item b)) -> [SpecTree a] -> f [SpecTree b]
traverseSpec Item a -> StateT Int Identity (Item b)
go [SpecTree a]
s
where
go :: Item a -> StateT Int Identity (Item b)
go Item a
item = (Int -> (Item b, Int)) -> StateT Int Identity (Item b)
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((Int -> (Item b, Int)) -> StateT Int Identity (Item b))
-> (Int -> (Item b, Int)) -> StateT Int Identity (Item b)
forall a b. (a -> b) -> a -> b
$ \Int
cnt -> (Int -> Item a -> Item b
f Int
cnt Item a
item, Int
cntInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
countItems :: [SpecTree a] -> Int
countItems :: forall a. [SpecTree a] -> Int
countItems [SpecTree a]
s = (State Int [SpecTree a] -> Int -> Int)
-> Int -> State Int [SpecTree a] -> Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip State Int [SpecTree a] -> Int -> Int
forall s a. State s a -> s -> s
execState Int
0 (State Int [SpecTree a] -> Int) -> State Int [SpecTree a] -> Int
forall a b. (a -> b) -> a -> b
$ (Item a -> StateT Int Identity (Item a))
-> [SpecTree a] -> State Int [SpecTree a]
forall (f :: * -> *) a b.
Applicative f =>
(Item a -> f (Item b)) -> [SpecTree a] -> f [SpecTree b]
traverseSpec Item a -> StateT Int Identity (Item a)
forall {m :: * -> *} {s} {a}. (Monad m, Num s) => a -> StateT s m a
go [SpecTree a]
s
where
go :: a -> StateT s m a
go a
item = (s -> (a, s)) -> StateT s m a
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((s -> (a, s)) -> StateT s m a) -> (s -> (a, s)) -> StateT s m a
forall a b. (a -> b) -> a -> b
$ \s
cnt -> (a
item, s
cnts -> s -> s
forall a. Num a => a -> a -> a
+s
1)