Skip to content

Commit

Permalink
sandwich-webdriver: moving video stuff around + trying to do support …
Browse files Browse the repository at this point in the history
…video flags
  • Loading branch information
thomasjm committed Oct 29, 2024
1 parent 616a211 commit e295a2e
Show file tree
Hide file tree
Showing 6 changed files with 78 additions and 18 deletions.
4 changes: 2 additions & 2 deletions sandwich-webdriver/sandwich-webdriver.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -54,10 +54,10 @@ library
Test.Sandwich.WebDriver.Internal.Screenshots
Test.Sandwich.WebDriver.Internal.StartWebDriver
Test.Sandwich.WebDriver.Internal.Types
Test.Sandwich.WebDriver.Internal.Types.Video
Test.Sandwich.WebDriver.Internal.Util
Test.Sandwich.WebDriver.Internal.Video
Test.Sandwich.WebDriver.Types
Test.Sandwich.WebDriver.Video.Internal
Test.Sandwich.WebDriver.Video.Types
Paths_sandwich_webdriver
hs-source-dirs:
src
Expand Down
13 changes: 11 additions & 2 deletions sandwich-webdriver/src/Test/Sandwich/WebDriver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@ module Test.Sandwich.WebDriver (
, webdriverSession
, WebDriverSession
, HasWebDriverSessionContext

-- * Shorthands
-- | These are used to make type signatures shorter.
, BaseMonad
Expand Down Expand Up @@ -90,6 +91,9 @@ import qualified Test.WebDriver.Config as W
import qualified Test.WebDriver.Session as W
import UnliftIO.MVar

-- import Control.Monad.Catch (MonadMask)
-- import Test.Sandwich.WebDriver.Video (recordVideoInExampleT)


-- | Introduce a 'WebDriver', using the given 'WebDriverDependencies'.
-- A good default is 'defaultWebDriverDependencies'.
Expand Down Expand Up @@ -208,14 +212,19 @@ withSession session (ExampleT readerMonad) = do
-- We could do the same here, but it's not clear that it's needed.
let f :: m a -> m a = id

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

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

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

-- | Get all existing session names.
Expand Down
9 changes: 7 additions & 2 deletions sandwich-webdriver/src/Test/Sandwich/WebDriver/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module Test.Sandwich.WebDriver.Config (
, getDisplayNumber
, getDownloadDirectory
, getWebDriverName
, getXvfbSession

-- * Xvfb mode
, XvfbConfig
Expand All @@ -35,12 +36,16 @@ module Test.Sandwich.WebDriver.Config (
, headlessFirefoxCapabilities

-- * Types
, WhenToSave(..)
, RunMode(..)
-- ** BrowserDependencies
, browserDependencies
, BrowserDependenciesSpec(..)
, BrowserDependencies(..)
, HasBrowserDependencies
-- ** Xvfb
, XvfbSession(..)
-- ** Miscellaneous
, WhenToSave(..)
, RunMode(..)
) where

import Test.Sandwich.WebDriver.Internal.Capabilities
Expand Down
55 changes: 48 additions & 7 deletions sandwich-webdriver/src/Test/Sandwich/WebDriver/Video.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,8 @@ module Test.Sandwich.WebDriver.Video (
, startVideoRecording
, endVideoRecording

-- * Helpers
, getXvfbSession
-- * Wrap an ExampleT to conditionally record video
-- , recordVideoInExampleT

-- * Configuration
, VideoSettings(..)
Expand All @@ -22,9 +22,6 @@ module Test.Sandwich.WebDriver.Video (
, defaultAvfoundationOptions
, defaultGdigrabOptions

-- * Re-exports
, XvfbSession(..)

-- * Types
, BaseVideoConstraints
) where
Expand All @@ -41,14 +38,18 @@ import System.IO
import System.Process
import Test.Sandwich
import Test.Sandwich.WebDriver.Internal.Types
import Test.Sandwich.WebDriver.Internal.Types.Video
import Test.Sandwich.WebDriver.Internal.Video
import Test.Sandwich.WebDriver.Types
import Test.Sandwich.WebDriver.Video.Internal
import Test.Sandwich.WebDriver.Video.Types
import Test.Sandwich.WebDriver.Windows
import Test.WebDriver.Class as W
import Test.WebDriver.Commands
import UnliftIO.Exception

-- import Control.Monad.Trans.Control (MonadBaseControl)
-- import Data.Function
-- import UnliftIO.Directory


type BaseVideoConstraints context m = (
MonadLoggerIO m, MonadUnliftIO m, MonadMask m
Expand Down Expand Up @@ -132,3 +133,43 @@ endVideoRecording p = do
ExitFailure 255 -> return ()

ExitFailure n -> debug [i|ffmpeg exited with unexpected exit code #{n}'|]

-- * Wrappers

-- recordVideoInExampleT :: (
-- MonadUnliftIO m, MonadMask m, MonadBaseControl IO m
-- , HasBaseContext ctx, HasWebDriverContext ctx, HasWebDriverSessionContext ctx, HasSomeCommandLineOptions ctx
-- ) => String -> ExampleT ctx m a -> ExampleT ctx m a
-- recordVideoInExampleT browser action = do
-- getCurrentFolder >>= \case
-- Nothing -> action
-- Just folder -> do
-- SomeCommandLineOptions (CommandLineOptions {optWebdriverOptions=(CommandLineWebdriverOptions {..})}) <- getSomeCommandLineOptions
-- if | optIndividualVideos -> withVideo folder browser action
-- | optErrorVideos -> withVideoIfException folder browser action
-- | otherwise -> action

-- withVideo :: (
-- MonadUnliftIO m, MonadMask m, MonadBaseControl IO m
-- , HasBaseContext ctx, HasWebDriverContext ctx, HasWebDriverSessionContext ctx
-- ) => FilePath -> String -> ExampleT ctx m a -> ExampleT ctx m a
-- withVideo folder browser action = do
-- path <- getPathInFolder folder browser
-- bracket (startBrowserVideoRecording path defaultVideoSettings) endVideoRecording (const action)

-- withVideoIfException :: (
-- MonadUnliftIO m, MonadMask m, MonadBaseControl IO m
-- , HasBaseContext ctx, HasWebDriverContext ctx, HasWebDriverSessionContext ctx
-- ) => FilePath -> String -> ExampleT ctx m a -> ExampleT ctx m a
-- withVideoIfException folder browser action = do
-- path <- getPathInFolder folder browser
-- tryAny (bracket (startBrowserVideoRecording path defaultVideoSettings) (endVideoRecording) (const action)) >>= \case
-- Right ret -> removePathForcibly path >> return ret
-- Left e -> throwIO e

-- getPathInFolder :: (MonadUnliftIO m) => [Char] -> String -> m FilePath
-- getPathInFolder folder browser = flip fix (0 :: Integer) $ \loop n -> do
-- let path = folder </> [i|#{browser}_video_#{n}|]
-- liftIO (doesFileExist (path <> videoExtension)) >>= \case
-- False -> return path
-- True -> loop (n + 1)
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
{-# LANGUAGE CPP #-}

module Test.Sandwich.WebDriver.Internal.Video where
module Test.Sandwich.WebDriver.Video.Internal (
getVideoArgs
, videoExtension
) where

import Control.Monad.Catch (MonadMask)
import Control.Monad.IO.Unlift
Expand All @@ -13,8 +16,8 @@ import Test.Sandwich
import Test.Sandwich.WebDriver.Internal.Binaries.Ffmpeg
import Test.Sandwich.WebDriver.Internal.OnDemand
import Test.Sandwich.WebDriver.Internal.Types
import Test.Sandwich.WebDriver.Internal.Types.Video
import Test.Sandwich.WebDriver.Types
import Test.Sandwich.WebDriver.Video.Types

#ifdef darwin_HOST_OS
getMacScreenNumber :: IO (Maybe Int)
Expand All @@ -29,6 +32,9 @@ import UnliftIO.Environment
#endif


videoExtension :: String
videoExtension = ".avi"

getVideoArgs :: (
MonadUnliftIO m, MonadLoggerIO m, MonadMask m
, MonadReader context m, HasBaseContext context, HasWebDriverContext context
Expand All @@ -51,7 +57,7 @@ getVideoArgs path (width, height, x, y) (VideoSettings {..}) maybeXvfbSession =
& (("XAUTHORITY", xvfbXauthority) :)
& L.nubBy ((==) `on` fst)

let videoPath = [i|#{path}.avi|]
let videoPath = [i|#{path}#{videoExtension}|]

let cmd = ["-y"
, "-nostdin"
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@

module Test.Sandwich.WebDriver.Internal.Types.Video where

module Test.Sandwich.WebDriver.Video.Types where


-- | Default options for fast X11 video recording.
Expand Down

0 comments on commit e295a2e

Please sign in to comment.