Skip to content

Commit

Permalink
sandwich-webdriver: haddocks progress
Browse files Browse the repository at this point in the history
  • Loading branch information
thomasjm committed Oct 17, 2024
1 parent a4e99e0 commit 42bb510
Show file tree
Hide file tree
Showing 8 changed files with 80 additions and 25 deletions.
39 changes: 29 additions & 10 deletions sandwich-webdriver/linux-src/Test/Sandwich/WebDriver/Resolution.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,10 @@
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

{-|
Helper module to obtain the current display resolution. This is useful for positioning windows or setting up video recording.
-}


module Test.Sandwich.WebDriver.Resolution (
getResolution
, getResolutionForDisplay
Expand All @@ -18,21 +23,35 @@ import System.Process
import Text.Regex.TDFA


-- | Previously we got the screen resolution on Linux using the X11 Haskell library.
-- | Note: previously we got the screen resolution on Linux using the X11 Haskell library.
--
-- This was a troublesome dependency because it wouldn't build on Hackage, forcing us to upload
-- sandwich-webdriver documentation manually.
-- the documentation manually.
--
-- It also caused problems when trying to make the demos easy to run on a clean machine or a Mac.
-- Instead, we implement platform-specific getResolution functions.
-- On Linux, the simplest way seems to be to parse the output of xrandr. This is the approach taken by
-- at least one other library: https://github.com/davidmarkclements/screenres/blob/master/linux.cc
-- The other way to do it would be to load the x11 and/or xinerama libraries like is done here:
-- https://github.com/rr-/screeninfo/blob/master/screeninfo/enumerators/xinerama.py
-- but again, that would require users to install those libraries. xrandr itself seems like an easier
-- So instead, we now implement platform-specific 'getResolution' functions.
--
-- On Linux, the simplest way seems to be to parse the output of @xrandr@. This is the approach taken by
-- at least one other library called [screenres](https://github.com/davidmarkclements/screenres/blob/master/linux.cc).
-- The other way to do it would be to load the x11 and/or xinerama libraries like is done in
-- [screeninfo](https://github.com/rr-/screeninfo/blob/master/screeninfo/enumerators/xinerama.py),
-- but again, that would require users to install those libraries. Just using @xrandr@ itself seems like an easier
-- dependency.
getResolution :: (HasCallStack) => IO (Int, Int, Int, Int)
getResolution :: (
HasCallStack
)
-- | Returns (x, y, width, height)
=> IO (Int, Int, Int, Int)
getResolution = getResolution' Nothing

getResolutionForDisplay :: Int -> IO (Int, Int, Int, Int)
-- | Get the resolution for a specific display.
getResolutionForDisplay :: (
HasCallStack
)
-- | Display number
=> Int
-- | Returns (x, y, width, height)
-> IO (Int, Int, Int, Int)
getResolutionForDisplay n = getResolution' (Just [("DISPLAY", ":" <> show n)])

-- | Note: this doesn't pick up display scaling on Ubuntu 20.04.
Expand Down
10 changes: 7 additions & 3 deletions sandwich-webdriver/src/Test/Sandwich/WebDriver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,10 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

{-|
Introduce [WebDriver](https://www.selenium.dev/documentation/webdriver/) servers and sessions.
-}

module Test.Sandwich.WebDriver (
-- * Introducing a WebDriver server
introduceWebDriver
Expand Down Expand Up @@ -35,7 +39,7 @@ module Test.Sandwich.WebDriver (
, introduceWebDriver'
, addCommandLineOptionsToWdOptions

-- * Context types
-- * Types
, webdriver
, WebDriver
, HasWebDriverContext
Expand Down Expand Up @@ -191,11 +195,11 @@ withSession session (ExampleT readerMonad) = do

ExampleT (withReaderT (\ctx -> LabelValue (session, ref) :> ctx) $ mapReaderT (mapLoggingT f) readerMonad)

-- | Convenience function. 'withSession1' = 'withSession' "session1".
-- | Convenience function. @withSession1 = withSession "session1"@.
withSession1 :: WebDriverMonad m context => ExampleT (LabelValue "webdriverSession" WebDriverSession :> context) m a -> ExampleT context m a
withSession1 = withSession "session1"

-- | Convenience function. 'withSession2' = 'withSession' "session2".
-- | Convenience function. @withSession2 = withSession "session2"@.
withSession2 :: WebDriverMonad m context => ExampleT (LabelValue "webdriverSession" WebDriverSession :> context) m a -> ExampleT context m a
withSession2 = withSession "session2"

Expand Down
31 changes: 29 additions & 2 deletions sandwich-webdriver/src/Test/Sandwich/WebDriver/Binaries.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,20 +2,47 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}

{-|
Obtain various binaries you might need for WebDriver testing.
-}

module Test.Sandwich.WebDriver.Binaries (
-- * Selenium
obtainSelenium
, downloadSeleniumIfNecessary
, SeleniumToUse(..)

-- * Chrome
, obtainChrome
, ChromeToUse(..)
, ChromeVersion(..)

-- * Chrome driver
, obtainChromeDriver
, ChromeDriverToUse(..)
, downloadChromeDriverIfNecessary
, ChromeDriverVersion(..)

-- * Firefox
, obtainFirefox
, FirefoxToUse(..)

-- * Geckodriver
, obtainGeckoDriver
, GeckoDriverToUse(..)
, GeckoDriverVersion(..)

-- * Ffmpeg
, obtainFfmpeg
, FfmpegToUse(..)

-- * Xvfb
, obtainXvfb
, XvfbDependenciesSpec(..)
, XvfbToUse(..)
, FluxboxToUse(..)
) where

import Test.Sandwich.WebDriver.Internal.Binaries.Chrome
import Test.Sandwich.WebDriver.Internal.Binaries.Ffmpeg
import Test.Sandwich.WebDriver.Internal.Binaries.Firefox
import Test.Sandwich.WebDriver.Internal.Binaries.Selenium
import Test.Sandwich.WebDriver.Internal.Binaries.Xvfb
4 changes: 0 additions & 4 deletions sandwich-webdriver/src/Test/Sandwich/WebDriver/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,10 +50,6 @@ module Test.Sandwich.WebDriver.Config (
) where

import Test.Sandwich.WebDriver.Binaries
import Test.Sandwich.WebDriver.Internal.Binaries.Chrome
import Test.Sandwich.WebDriver.Internal.Binaries.Ffmpeg
import Test.Sandwich.WebDriver.Internal.Binaries.Firefox
import Test.Sandwich.WebDriver.Internal.Binaries.Xvfb
import Test.Sandwich.WebDriver.Internal.Capabilities
import Test.Sandwich.WebDriver.Internal.Dependencies
import Test.Sandwich.WebDriver.Internal.Types
Original file line number Diff line number Diff line change
Expand Up @@ -55,11 +55,14 @@ obtainChrome (UseChromeAt p) = doesFileExist p >>= \case
obtainChrome (UseChromeFromNixpkgs nixContext) =
Right <$> getBinaryViaNixPackage' @"google-chrome-stable" nixContext "google-chrome"

-- | Manually obtain a chromedriver binary, according to the 'ChromeDriverToUse' policy.
-- | Manually obtain a @chromedriver@ binary, according to the 'ChromeDriverToUse' policy.
obtainChromeDriver :: (
MonadReader context m, HasBaseContext context
, MonadUnliftIO m, MonadLogger m
) => ChromeDriverToUse -> m (Either T.Text FilePath)
)
-- | How to obtain @chromedriver@
=> ChromeDriverToUse
-> m (Either T.Text FilePath)
obtainChromeDriver (DownloadChromeDriverFrom toolsDir url) = do
let path = [i|#{toolsDir}/#{chromeDriverExecutable}|]
unlessM (liftIO $ doesFileExist path) $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -42,12 +42,15 @@ obtainFirefox (UseFirefoxAt p) = doesFileExist p >>= \case
obtainFirefox (UseFirefoxFromNixpkgs nixContext) =
Right <$> getBinaryViaNixPackage' @"firefox" nixContext "firefox"

-- | Manually obtain a geckodriver binary, according to the 'GeckoDriverToUse' policy,
-- | Manually obtain a @geckodriver@ binary, according to the 'GeckoDriverToUse' policy,
-- storing it under the provided 'FilePath' if necessary and returning the exact path.
obtainGeckoDriver :: (
MonadReader context m, HasBaseContext context
, MonadUnliftIO m, MonadLogger m
) => GeckoDriverToUse -> m (Either T.Text FilePath)
)
-- | How to obtain @geckodriver@
=> GeckoDriverToUse
-> m (Either T.Text FilePath)
obtainGeckoDriver (DownloadGeckoDriverFrom toolsDir url) = do
let path = [i|#{toolsDir}/#{geckoDriverExecutable}|]
unlessM (liftIO $ doesFileExist path) $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,10 @@ defaultSeleniumJarUrl = "https://selenium-release.storage.googleapis.com/3.141/s
obtainSelenium :: (
MonadReader context m, HasBaseContext context
, MonadUnliftIO m, MonadLogger m
) => SeleniumToUse -> m FilePath
)
-- | How to obtain Selenium
=> SeleniumToUse
-> m FilePath
obtainSelenium (DownloadSeleniumFrom toolsDir url) = do
let path = [i|#{toolsDir}/selenium-server-standalone.jar|]
unlessM (liftIO $ doesFileExist path) $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ data BrowserDependenciesSpec = BrowserDependenciesSpecChrome {
-- * Download Selenium to @\/tmp\/tools@, reusing the one there if found.
-- * Use @firefox@ from the PATH as the browser.
-- * Download a compatible @geckodriver@ to @\/tmp\/tools@, reusing the one there if found.
-- * If applicable, it will also get `xvfb-run`, `fluxbox`, and/or `ffmpeg` from the PATH.
-- * If applicable, it will also get @xvfb-run@, @fluxbox@, and/or @ffmpeg@ from the PATH.
--
-- But, it's easy to customize this behavior. You can define your own 'WebDriverDependencies' and customize
-- how each of these dependencies are found.
Expand Down

0 comments on commit 42bb510

Please sign in to comment.