{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Test.Sandwich.WebDriver (
introduceWebDriver
, introduceWebDriverViaNix
, introduceWebDriverViaNix'
, defaultWebDriverDependencies
, WebDriverDependencies(..)
, withSession
, withSession1
, withSession2
, getSessions
, closeCurrentSession
, closeSession
, closeAllSessions
, closeAllSessionsExcept
, Session
, allocateWebDriver
, cleanupWebDriver
, introduceBrowserDependenciesViaNix
, introduceBrowserDependenciesViaNix'
, introduceWebDriver'
, addCommandLineOptionsToWdOptions
, webdriver
, WebDriver
, HasWebDriverContext
, webdriverSession
, WebDriverSession
, HasWebDriverSessionContext
, BaseMonad
, ContextWithBaseDeps
, ContextWithWebdriverDeps
, WebDriverMonad
, WebDriverSessionMonad
, OnDemandOptions
, defaultOnDemandOptions
, module Test.Sandwich.WebDriver.Config
) where
import Control.Monad.Catch (MonadMask)
import Control.Monad.IO.Class
import Control.Monad.Reader
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.IORef
import qualified Data.List as L
import qualified Data.Map as M
import Data.Maybe
import Data.String.Interpolate
import Test.Sandwich
import Test.Sandwich.Contexts.Files
import Test.Sandwich.Contexts.Nix
import Test.Sandwich.WebDriver.Binaries
import Test.Sandwich.WebDriver.Config
import Test.Sandwich.WebDriver.Internal.Action
import Test.Sandwich.WebDriver.Internal.Dependencies
import Test.Sandwich.WebDriver.Internal.StartWebDriver
import Test.Sandwich.WebDriver.Internal.Types
import Test.Sandwich.WebDriver.Types
import Test.Sandwich.WebDriver.Video (recordVideoIfConfigured)
import qualified Test.WebDriver as W
import qualified Test.WebDriver.Config as W
import qualified Test.WebDriver.Session as W
import UnliftIO.MVar
introduceWebDriver :: forall context m. (
BaseMonad m context, HasSomeCommandLineOptions context
)
=> WebDriverDependencies
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m () -> SpecFree context m ()
introduceWebDriver :: forall context (m :: * -> *).
(BaseMonad m context, HasSomeCommandLineOptions context) =>
WebDriverDependencies
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriver WebDriverDependencies
wdd WdOptions
wdOptions = WebDriverDependencies
-> (WdOptions
-> ExampleT (ContextWithBaseDeps context) m WebDriver)
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
forall (m :: * -> *) context.
BaseMonad m context =>
WebDriverDependencies
-> (WdOptions
-> ExampleT (ContextWithBaseDeps context) m WebDriver)
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriver' WebDriverDependencies
wdd WdOptions
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
WebDriver
WdOptions -> ExampleT (ContextWithBaseDeps context) m WebDriver
forall {m :: * -> *} {context}.
(MonadUnliftIO m, MonadMask m, HasBaseContext context,
HasSomeCommandLineOptions context, HasBrowserDependencies context,
HasLabel
context "file-selenium.jar" (EnvironmentFile "selenium.jar"),
HasLabel context "file-java" (EnvironmentFile "java")) =>
WdOptions -> ExampleT context m WebDriver
alloc WdOptions
wdOptions
where
alloc :: WdOptions -> ExampleT context m WebDriver
alloc WdOptions
wdOptions' = do
SomeCommandLineOptions
clo <- ExampleT context m SomeCommandLineOptions
forall context (m :: * -> *).
(HasSomeCommandLineOptions context, MonadReader context m) =>
m SomeCommandLineOptions
getSomeCommandLineOptions
WdOptions -> OnDemandOptions -> ExampleT context m WebDriver
forall (m :: * -> *) context.
(BaseMonad m context, HasFile context "java",
HasFile context "selenium.jar", HasBrowserDependencies context) =>
WdOptions -> OnDemandOptions -> ExampleT context m WebDriver
allocateWebDriver (SomeCommandLineOptions -> WdOptions -> WdOptions
addCommandLineOptionsToWdOptions SomeCommandLineOptions
clo WdOptions
wdOptions') OnDemandOptions
onDemandOptions
onDemandOptions :: OnDemandOptions
onDemandOptions = OnDemandOptions {
ffmpegToUse :: FfmpegToUse
ffmpegToUse = WebDriverDependencies -> FfmpegToUse
webDriverFfmpeg WebDriverDependencies
wdd
, xvfbToUse :: XvfbToUse
xvfbToUse = XvfbDependenciesSpec -> XvfbToUse
xvfbDependenciesSpecXvfb (XvfbDependenciesSpec -> XvfbToUse)
-> XvfbDependenciesSpec -> XvfbToUse
forall a b. (a -> b) -> a -> b
$ WebDriverDependencies -> XvfbDependenciesSpec
webDriverXvfb WebDriverDependencies
wdd
}
introduceWebDriverViaNix :: forall m context. (
BaseMonad m context, HasSomeCommandLineOptions context, HasNixContext context
)
=> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriverViaNix :: forall (m :: * -> *) context.
(BaseMonad m context, HasSomeCommandLineOptions context,
HasNixContext context) =>
WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriverViaNix = NodeOptions
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
forall (m :: * -> *) context.
(BaseMonad m context, HasSomeCommandLineOptions context,
HasNixContext context) =>
NodeOptions
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriverViaNix' (NodeOptions
defaultNodeOptions { nodeOptionsVisibilityThreshold = defaultFileContextVisibilityThreshold })
introduceWebDriverViaNix' :: forall m context. (
BaseMonad m context, HasSomeCommandLineOptions context, HasNixContext context
)
=> NodeOptions
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriverViaNix' :: forall (m :: * -> *) context.
(BaseMonad m context, HasSomeCommandLineOptions context,
HasNixContext context) =>
NodeOptions
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriverViaNix' NodeOptions
nodeOptions WdOptions
wdOptions =
forall (a :: Symbol) context (m :: * -> *).
(HasBaseContext context, HasNixContext context, MonadUnliftIO m,
KnownSymbol a) =>
NodeOptions
-> NixPackageName
-> (FilePath -> IO FilePath)
-> SpecFree
(LabelValue (AppendSymbol "file-" a) (EnvironmentFile a)
:> context)
m
()
-> SpecFree context m ()
introduceFileViaNixPackage'' @"selenium.jar" NodeOptions
nodeOptions NixPackageName
"selenium-server-standalone" ((FilePath -> IO Bool) -> FilePath -> IO FilePath
findFirstFile (Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> (FilePath -> Bool) -> FilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
".jar" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isSuffixOf`)))
(Free
(SpecCommand
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m)
()
-> SpecFree context m ())
-> (SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> Free
(SpecCommand
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m)
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree context m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: Symbol) context (m :: * -> *).
(HasBaseContext context, HasNixContext context, MonadUnliftIO m,
KnownSymbol a) =>
NodeOptions
-> NixPackageName
-> SpecFree
(LabelValue (AppendSymbol "file-" a) (EnvironmentFile a)
:> context)
m
()
-> SpecFree context m ()
introduceBinaryViaNixPackage' @"java" NodeOptions
nodeOptions NixPackageName
"jre"
(Free
(SpecCommand
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m)
()
-> Free
(SpecCommand
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m)
())
-> (SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> Free
(SpecCommand
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m)
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> Free
(SpecCommand
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m)
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeOptions
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
-> Free
(SpecCommand
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m)
()
forall (m :: * -> *) context.
(MonadUnliftIO m, HasBaseContext context, HasNixContext context,
HasSomeCommandLineOptions context) =>
NodeOptions
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies :> context)
m
()
-> SpecFree context m ()
introduceBrowserDependenciesViaNix' NodeOptions
nodeOptions
(SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
-> Free
(SpecCommand
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m)
())
-> (SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> Free
(SpecCommand
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m)
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath
-> Label "webdriver" WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
WebDriver
-> (HasCallStack =>
WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
forall intro (l :: Symbol) context (m :: * -> *).
(HasCallStack, Typeable intro) =>
FilePath
-> Label l intro
-> ExampleT context m intro
-> (HasCallStack => intro -> ExampleT context m ())
-> SpecFree (LabelValue l intro :> context) m ()
-> SpecFree context m ()
introduce FilePath
"Introduce WebDriver session" Label "webdriver" WebDriver
webdriver ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
WebDriver
alloc HasCallStack =>
WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
forall (m :: * -> *) context.
BaseMonad m context =>
WebDriver -> ExampleT context m ()
cleanupWebDriver
where
alloc :: ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
WebDriver
alloc = do
SomeCommandLineOptions
clo <- ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
SomeCommandLineOptions
forall context (m :: * -> *).
(HasSomeCommandLineOptions context, MonadReader context m) =>
m SomeCommandLineOptions
getSomeCommandLineOptions
NixContext
nc <- Label "nixContext" NixContext
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
NixContext
forall context (l :: Symbol) a (m :: * -> *).
(HasLabel context l a, MonadReader context m) =>
Label l a -> m a
getContext Label "nixContext" NixContext
nixContext
let onDemandOptions :: OnDemandOptions
onDemandOptions = OnDemandOptions {
ffmpegToUse :: FfmpegToUse
ffmpegToUse = NixContext -> FfmpegToUse
UseFfmpegFromNixpkgs NixContext
nc
, xvfbToUse :: XvfbToUse
xvfbToUse = NixContext -> XvfbToUse
UseXvfbFromNixpkgs NixContext
nc
}
WdOptions
-> OnDemandOptions
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
WebDriver
forall (m :: * -> *) context.
(BaseMonad m context, HasFile context "java",
HasFile context "selenium.jar", HasBrowserDependencies context) =>
WdOptions -> OnDemandOptions -> ExampleT context m WebDriver
allocateWebDriver (SomeCommandLineOptions -> WdOptions -> WdOptions
addCommandLineOptionsToWdOptions SomeCommandLineOptions
clo WdOptions
wdOptions) OnDemandOptions
onDemandOptions
introduceWebDriver' :: forall m context. (
BaseMonad m context
)
=> WebDriverDependencies
-> (WdOptions -> ExampleT (ContextWithBaseDeps context) m WebDriver)
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m () -> SpecFree context m ()
introduceWebDriver' :: forall (m :: * -> *) context.
BaseMonad m context =>
WebDriverDependencies
-> (WdOptions
-> ExampleT (ContextWithBaseDeps context) m WebDriver)
-> WdOptions
-> SpecFree (ContextWithWebdriverDeps context) m ()
-> SpecFree context m ()
introduceWebDriver' (WebDriverDependencies {Maybe FilePath
FfmpegToUse
SeleniumToUse
XvfbDependenciesSpec
BrowserDependenciesSpec
webDriverFfmpeg :: WebDriverDependencies -> FfmpegToUse
webDriverXvfb :: WebDriverDependencies -> XvfbDependenciesSpec
webDriverDependencyJava :: Maybe FilePath
webDriverDependencySelenium :: SeleniumToUse
webDriverDependencyBrowser :: BrowserDependenciesSpec
webDriverXvfb :: XvfbDependenciesSpec
webDriverFfmpeg :: FfmpegToUse
webDriverDependencyBrowser :: WebDriverDependencies -> BrowserDependenciesSpec
webDriverDependencySelenium :: WebDriverDependencies -> SeleniumToUse
webDriverDependencyJava :: WebDriverDependencies -> Maybe FilePath
..}) WdOptions -> ExampleT (ContextWithBaseDeps context) m WebDriver
alloc WdOptions
wdOptions =
FilePath
-> Label "file-selenium.jar" (EnvironmentFile "selenium.jar")
-> ExampleT context m (EnvironmentFile "selenium.jar")
-> (HasCallStack =>
EnvironmentFile "selenium.jar" -> ExampleT context m ())
-> SpecFree
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m
()
-> SpecFree context m ()
forall intro (l :: Symbol) context (m :: * -> *).
(HasCallStack, Typeable intro) =>
FilePath
-> Label l intro
-> ExampleT context m intro
-> (HasCallStack => intro -> ExampleT context m ())
-> SpecFree (LabelValue l intro :> context) m ()
-> SpecFree context m ()
introduce FilePath
"Introduce selenium.jar" (forall (a :: Symbol).
Label (AppendSymbol "file-" a) (EnvironmentFile a)
mkFileLabel @"selenium.jar") ((FilePath -> EnvironmentFile "selenium.jar"
forall {k} (a :: k). FilePath -> EnvironmentFile a
EnvironmentFile (FilePath -> EnvironmentFile "selenium.jar")
-> ExampleT context m FilePath
-> ExampleT context m (EnvironmentFile "selenium.jar")
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (ExampleT context m FilePath
-> ExampleT context m (EnvironmentFile "selenium.jar"))
-> ExampleT context m FilePath
-> ExampleT context m (EnvironmentFile "selenium.jar")
forall a b. (a -> b) -> a -> b
$ SeleniumToUse -> ExampleT context m FilePath
forall context (m :: * -> *).
(MonadReader context m, HasBaseContext context, MonadUnliftIO m,
MonadLogger m) =>
SeleniumToUse -> m FilePath
obtainSelenium SeleniumToUse
webDriverDependencySelenium) (ExampleT context m ()
-> EnvironmentFile "selenium.jar" -> ExampleT context m ()
forall a b. a -> b -> a
const (ExampleT context m ()
-> EnvironmentFile "selenium.jar" -> ExampleT context m ())
-> ExampleT context m ()
-> EnvironmentFile "selenium.jar"
-> ExampleT context m ()
forall a b. (a -> b) -> a -> b
$ () -> ExampleT context m ()
forall a. a -> ExampleT context m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
(SpecFree
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m
()
-> SpecFree context m ())
-> (SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree context m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (case Maybe FilePath
webDriverDependencyJava of Maybe FilePath
Nothing -> forall (a :: Symbol) context (m :: * -> *).
(MonadUnliftIO m, KnownSymbol a) =>
SpecFree
(LabelValue (AppendSymbol "file-" a) (EnvironmentFile a)
:> context)
m
()
-> SpecFree context m ()
introduceBinaryViaEnvironment @"java"; Just FilePath
p -> forall (a :: Symbol) context (m :: * -> *).
(MonadUnliftIO m, KnownSymbol a) =>
FilePath
-> SpecFree
(LabelValue (AppendSymbol "file-" a) (EnvironmentFile a)
:> context)
m
()
-> SpecFree context m ()
introduceFile @"java" FilePath
p)
(SpecFree
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
-> SpecFree
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m
())
-> (SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)
m
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath
-> Label "browserDependencies" BrowserDependencies
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
BrowserDependencies
-> (HasCallStack =>
BrowserDependencies
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
())
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
-> SpecFree
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
forall intro (l :: Symbol) context (m :: * -> *).
(HasCallStack, Typeable intro) =>
FilePath
-> Label l intro
-> ExampleT context m intro
-> (HasCallStack => intro -> ExampleT context m ())
-> SpecFree (LabelValue l intro :> context) m ()
-> SpecFree context m ()
introduce FilePath
"Introduce browser dependencies" Label "browserDependencies" BrowserDependencies
browserDependencies (BrowserDependenciesSpec
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
BrowserDependencies
forall context (m :: * -> *).
(MonadReader context m, HasBaseContext context, MonadUnliftIO m,
MonadLogger m) =>
BrowserDependenciesSpec -> m BrowserDependencies
getBrowserDependencies BrowserDependenciesSpec
webDriverDependencyBrowser) (ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
-> BrowserDependencies
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
forall a b. a -> b -> a
const (ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
-> BrowserDependencies
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
())
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
-> BrowserDependencies
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
forall a b. (a -> b) -> a -> b
$ ()
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
forall a.
a
-> ExampleT
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
(SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
-> SpecFree
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
())
-> (SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))
m
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath
-> Label "webdriver" WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
WebDriver
-> (HasCallStack =>
WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
())
-> SpecFree
(LabelValue "webdriver" WebDriver
:> (LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context))))
m
()
-> SpecFree
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
forall intro (l :: Symbol) context (m :: * -> *).
(HasCallStack, Typeable intro) =>
FilePath
-> Label l intro
-> ExampleT context m intro
-> (HasCallStack => intro -> ExampleT context m ())
-> SpecFree (LabelValue l intro :> context) m ()
-> SpecFree context m ()
introduce FilePath
"Introduce WebDriver session" Label "webdriver" WebDriver
webdriver (WdOptions -> ExampleT (ContextWithBaseDeps context) m WebDriver
alloc WdOptions
wdOptions) HasCallStack =>
WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
WebDriver
-> ExampleT
(LabelValue "browserDependencies" BrowserDependencies
:> (LabelValue "file-java" (EnvironmentFile "java")
:> (LabelValue "file-selenium.jar" (EnvironmentFile "selenium.jar")
:> context)))
m
()
forall (m :: * -> *) context.
BaseMonad m context =>
WebDriver -> ExampleT context m ()
cleanupWebDriver
allocateWebDriver :: (
BaseMonad m context
, HasFile context "java", HasFile context "selenium.jar", HasBrowserDependencies context
)
=> WdOptions
-> OnDemandOptions
-> ExampleT context m WebDriver
allocateWebDriver :: forall (m :: * -> *) context.
(BaseMonad m context, HasFile context "java",
HasFile context "selenium.jar", HasBrowserDependencies context) =>
WdOptions -> OnDemandOptions -> ExampleT context m WebDriver
allocateWebDriver WdOptions
wdOptions OnDemandOptions
onDemandOptions = do
FilePath
dir <- FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"/tmp" (Maybe FilePath -> FilePath)
-> ExampleT context m (Maybe FilePath)
-> ExampleT context m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ExampleT context m (Maybe FilePath)
forall context (m :: * -> *).
HasBaseContextMonad context m =>
m (Maybe FilePath)
getCurrentFolder
WdOptions
-> OnDemandOptions -> FilePath -> ExampleT context m WebDriver
forall (m :: * -> *) context.
(Constraints m, MonadReader context m, HasBaseContext context,
HasFile context "java", HasFile context "selenium.jar",
HasBrowserDependencies context) =>
WdOptions -> OnDemandOptions -> FilePath -> m WebDriver
startWebDriver WdOptions
wdOptions OnDemandOptions
onDemandOptions FilePath
dir
cleanupWebDriver :: (BaseMonad m context) => WebDriver -> ExampleT context m ()
cleanupWebDriver :: forall (m :: * -> *) context.
BaseMonad m context =>
WebDriver -> ExampleT context m ()
cleanupWebDriver WebDriver
sess = do
WebDriver -> ExampleT context m ()
forall (m :: * -> *).
(HasCallStack, MonadLogger m, MonadUnliftIO m) =>
WebDriver -> m ()
closeAllSessions WebDriver
sess
WebDriver -> ExampleT context m ()
forall (m :: * -> *). Constraints m => WebDriver -> m ()
stopWebDriver WebDriver
sess
withSession :: forall m context a. (
MonadMask m, MonadBaseControl IO m
, HasBaseContext context, HasSomeCommandLineOptions context, WebDriverMonad m context
)
=> Session
-> ExampleT (LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession :: forall (m :: * -> *) context a.
(MonadMask m, MonadBaseControl IO m, HasBaseContext context,
HasSomeCommandLineOptions context, WebDriverMonad m context) =>
FilePath
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession FilePath
session ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
action = do
WebDriver {FilePath
(ProcessHandle, Maybe XvfbSession)
MVar (Map FilePath WDSession)
MVar (OnDemand FilePath)
WDConfig
FfmpegToUse
XvfbToUse
WdOptions
wdName :: FilePath
wdWebDriver :: (ProcessHandle, Maybe XvfbSession)
wdOptions :: WdOptions
wdSessionMap :: MVar (Map FilePath WDSession)
wdConfig :: WDConfig
wdDownloadDir :: FilePath
wdFfmpegToUse :: FfmpegToUse
wdFfmpeg :: MVar (OnDemand FilePath)
wdXvfbToUse :: XvfbToUse
wdXvfb :: MVar (OnDemand FilePath)
wdXvfb :: WebDriver -> MVar (OnDemand FilePath)
wdXvfbToUse :: WebDriver -> XvfbToUse
wdFfmpeg :: WebDriver -> MVar (OnDemand FilePath)
wdFfmpegToUse :: WebDriver -> FfmpegToUse
wdDownloadDir :: WebDriver -> FilePath
wdConfig :: WebDriver -> WDConfig
wdSessionMap :: WebDriver -> MVar (Map FilePath WDSession)
wdOptions :: WebDriver -> WdOptions
wdWebDriver :: WebDriver -> (ProcessHandle, Maybe XvfbSession)
wdName :: WebDriver -> FilePath
..} <- Label "webdriver" WebDriver -> ExampleT context m WebDriver
forall context (l :: Symbol) a (m :: * -> *).
(HasLabel context l a, MonadReader context m) =>
Label l a -> m a
getContext Label "webdriver" WebDriver
webdriver
WDSession
sess <- MVar (Map FilePath WDSession)
-> (Map FilePath WDSession
-> ExampleT context m (Map FilePath WDSession, WDSession))
-> ExampleT context m WDSession
forall (m :: * -> *) a b.
MonadUnliftIO m =>
MVar a -> (a -> m (a, b)) -> m b
modifyMVar MVar (Map FilePath WDSession)
wdSessionMap ((Map FilePath WDSession
-> ExampleT context m (Map FilePath WDSession, WDSession))
-> ExampleT context m WDSession)
-> (Map FilePath WDSession
-> ExampleT context m (Map FilePath WDSession, WDSession))
-> ExampleT context m WDSession
forall a b. (a -> b) -> a -> b
$ \Map FilePath WDSession
sessionMap -> case FilePath -> Map FilePath WDSession -> Maybe WDSession
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup FilePath
session Map FilePath WDSession
sessionMap of
Just WDSession
sess -> (Map FilePath WDSession, WDSession)
-> ExampleT context m (Map FilePath WDSession, WDSession)
forall a. a -> ExampleT context m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Map FilePath WDSession
sessionMap, WDSession
sess)
Maybe WDSession
Nothing -> do
NixPackageName -> ExampleT context m ()
forall (m :: * -> *).
(HasCallStack, MonadLogger m) =>
NixPackageName -> m ()
debug [i|Creating session '#{session}'|]
WDSession
sess'' <- IO WDSession -> ExampleT context m WDSession
forall a. IO a -> ExampleT context m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WDSession -> ExampleT context m WDSession)
-> IO WDSession -> ExampleT context m WDSession
forall a b. (a -> b) -> a -> b
$ 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
wdConfig
let sess' :: WDSession
sess' = WDSession
sess'' { W.wdSessHistUpdate = W.unlimitedHistory }
WDSession
sess <- IO WDSession -> ExampleT context m WDSession
forall a. IO a -> ExampleT context m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WDSession -> ExampleT context m WDSession)
-> IO WDSession -> ExampleT context m WDSession
forall a b. (a -> b) -> a -> b
$ WDSession -> WD WDSession -> IO WDSession
forall a. WDSession -> WD a -> IO a
W.runWD WDSession
sess' (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
W.createSession (Capabilities -> WD WDSession) -> Capabilities -> WD WDSession
forall a b. (a -> b) -> a -> b
$ WDConfig -> Capabilities
W.wdCapabilities WDConfig
wdConfig
(Map FilePath WDSession, WDSession)
-> ExampleT context m (Map FilePath WDSession, WDSession)
forall a. a -> ExampleT context m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
-> WDSession -> Map FilePath WDSession -> Map FilePath WDSession
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert FilePath
session WDSession
sess Map FilePath WDSession
sessionMap, WDSession
sess)
IORef WDSession
ref <- IO (IORef WDSession) -> ExampleT context m (IORef WDSession)
forall a. IO a -> ExampleT context m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef WDSession) -> ExampleT context m (IORef WDSession))
-> IO (IORef WDSession) -> ExampleT context m (IORef WDSession)
forall a b. (a -> b) -> a -> b
$ WDSession -> IO (IORef WDSession)
forall a. a -> IO (IORef a)
newIORef WDSession
sess
Label "webdriverSession" WebDriverSession
-> WebDriverSession
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
forall (m :: * -> *) (l :: Symbol) a intro context.
Label l intro
-> intro
-> ExampleT (LabelValue l intro :> context) m a
-> ExampleT context m a
pushContext Label "webdriverSession" WebDriverSession
webdriverSession (FilePath
session, IORef WDSession
ref) (ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a)
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
forall a b. (a -> b) -> a -> b
$
FilePath
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
forall context (m :: * -> *) a.
(BaseVideoConstraints context m, WebDriver m,
HasSomeCommandLineOptions context) =>
FilePath -> m a -> m a
recordVideoIfConfigured FilePath
session ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
action
withSession1 :: (
MonadMask m, MonadBaseControl IO m
, HasBaseContext context, HasSomeCommandLineOptions context, WebDriverMonad m context
)
=> ExampleT (LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession1 :: forall (m :: * -> *) context a.
(MonadMask m, MonadBaseControl IO m, HasBaseContext context,
HasSomeCommandLineOptions context, WebDriverMonad m context) =>
ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession1 = FilePath
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
forall (m :: * -> *) context a.
(MonadMask m, MonadBaseControl IO m, HasBaseContext context,
HasSomeCommandLineOptions context, WebDriverMonad m context) =>
FilePath
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession FilePath
"session1"
withSession2 :: (
MonadMask m, MonadBaseControl IO m
, HasBaseContext context, HasSomeCommandLineOptions context, WebDriverMonad m context
)
=> ExampleT (LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession2 :: forall (m :: * -> *) context a.
(MonadMask m, MonadBaseControl IO m, HasBaseContext context,
HasSomeCommandLineOptions context, WebDriverMonad m context) =>
ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession2 = FilePath
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
forall (m :: * -> *) context a.
(MonadMask m, MonadBaseControl IO m, HasBaseContext context,
HasSomeCommandLineOptions context, WebDriverMonad m context) =>
FilePath
-> ExampleT
(LabelValue "webdriverSession" WebDriverSession :> context) m a
-> ExampleT context m a
withSession FilePath
"session2"
getSessions :: (MonadReader context m, WebDriverMonad m context) => m [Session]
getSessions :: forall context (m :: * -> *).
(MonadReader context m, WebDriverMonad m context) =>
m [FilePath]
getSessions = do
WebDriver {FilePath
(ProcessHandle, Maybe XvfbSession)
MVar (Map FilePath WDSession)
MVar (OnDemand FilePath)
WDConfig
FfmpegToUse
XvfbToUse
WdOptions
wdXvfb :: WebDriver -> MVar (OnDemand FilePath)
wdXvfbToUse :: WebDriver -> XvfbToUse
wdFfmpeg :: WebDriver -> MVar (OnDemand FilePath)
wdFfmpegToUse :: WebDriver -> FfmpegToUse
wdDownloadDir :: WebDriver -> FilePath
wdConfig :: WebDriver -> WDConfig
wdSessionMap :: WebDriver -> MVar (Map FilePath WDSession)
wdOptions :: WebDriver -> WdOptions
wdWebDriver :: WebDriver -> (ProcessHandle, Maybe XvfbSession)
wdName :: WebDriver -> FilePath
wdName :: FilePath
wdWebDriver :: (ProcessHandle, Maybe XvfbSession)
wdOptions :: WdOptions
wdSessionMap :: MVar (Map FilePath WDSession)
wdConfig :: WDConfig
wdDownloadDir :: FilePath
wdFfmpegToUse :: FfmpegToUse
wdFfmpeg :: MVar (OnDemand FilePath)
wdXvfbToUse :: XvfbToUse
wdXvfb :: MVar (OnDemand FilePath)
..} <- Label "webdriver" WebDriver -> m WebDriver
forall context (l :: Symbol) a (m :: * -> *).
(HasLabel context l a, MonadReader context m) =>
Label l a -> m a
getContext Label "webdriver" WebDriver
webdriver
Map FilePath WDSession -> [FilePath]
forall k a. Map k a -> [k]
M.keys (Map FilePath WDSession -> [FilePath])
-> m (Map FilePath WDSession) -> m [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (Map FilePath WDSession) -> m (Map FilePath WDSession)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MVar (Map FilePath WDSession) -> IO (Map FilePath WDSession)
forall (m :: * -> *) a. MonadIO m => MVar a -> m a
readMVar MVar (Map FilePath WDSession)
wdSessionMap)
addCommandLineOptionsToWdOptions :: SomeCommandLineOptions -> WdOptions -> WdOptions
addCommandLineOptionsToWdOptions :: SomeCommandLineOptions -> WdOptions -> WdOptions
addCommandLineOptionsToWdOptions (SomeCommandLineOptions (CommandLineOptions {optWebdriverOptions :: forall a. CommandLineOptions a -> CommandLineWebdriverOptions
optWebdriverOptions=(CommandLineWebdriverOptions {Bool
Maybe FilePath
Maybe BrowserToUse
Maybe DisplayType
optBrowserToUse :: Maybe BrowserToUse
optChromeNoSandbox :: Bool
optDisplay :: Maybe DisplayType
optFluxbox :: Bool
optIndividualVideos :: Bool
optErrorVideos :: Bool
optSeleniumJar :: Maybe FilePath
optChromeBinary :: Maybe FilePath
optChromeDriver :: Maybe FilePath
optFirefoxBinary :: Maybe FilePath
optGeckoDriver :: Maybe FilePath
optGeckoDriver :: CommandLineWebdriverOptions -> Maybe FilePath
optFirefoxBinary :: CommandLineWebdriverOptions -> Maybe FilePath
optChromeDriver :: CommandLineWebdriverOptions -> Maybe FilePath
optChromeBinary :: CommandLineWebdriverOptions -> Maybe FilePath
optSeleniumJar :: CommandLineWebdriverOptions -> Maybe FilePath
optErrorVideos :: CommandLineWebdriverOptions -> Bool
optIndividualVideos :: CommandLineWebdriverOptions -> Bool
optFluxbox :: CommandLineWebdriverOptions -> Bool
optDisplay :: CommandLineWebdriverOptions -> Maybe DisplayType
optChromeNoSandbox :: CommandLineWebdriverOptions -> Bool
optBrowserToUse :: CommandLineWebdriverOptions -> Maybe BrowserToUse
..})})) wdOptions :: WdOptions
wdOptions@(WdOptions {Bool
Int
Maybe Manager
Capabilities
RunMode
WhenToSave
capabilities :: Capabilities
saveSeleniumMessageHistory :: WhenToSave
runMode :: RunMode
httpManager :: Maybe Manager
httpRetryCount :: Int
chromeNoSandbox :: Bool
chromeNoSandbox :: WdOptions -> Bool
httpRetryCount :: WdOptions -> Int
httpManager :: WdOptions -> Maybe Manager
runMode :: WdOptions -> RunMode
saveSeleniumMessageHistory :: WdOptions -> WhenToSave
capabilities :: WdOptions -> Capabilities
..}) = WdOptions
wdOptions {
runMode = case optDisplay of
Maybe DisplayType
Nothing -> RunMode
runMode
Just DisplayType
Headless -> HeadlessConfig -> RunMode
RunHeadless HeadlessConfig
defaultHeadlessConfig
Just DisplayType
Xvfb -> XvfbConfig -> RunMode
RunInXvfb (XvfbConfig
defaultXvfbConfig { xvfbStartFluxbox = optFluxbox })
Just DisplayType
Current -> RunMode
Normal
, chromeNoSandbox = optChromeNoSandbox
}