-------------------------------------------------------------------- -- | -- Module : Selenium.Interactive -- Copyright : (c) Galois, Inc. 2007 -- License : BSD3 -- -- Maintainer: Aaron Tomb -- Stability : provisional -- Portability: non-portable (multi-parameter type classes) -- -- Utility functions to ease interactive use inside GHCi. -- -------------------------------------------------------------------- module Selenium.Interactive ( start, stop, ($$), ) where import Control.Monad.Error import Data.Maybe import Network.BSD import Network.URI import Selenium.Server infixr 0 $$ -- | Starts up a session and returns a wrapper function that will run -- commands. start :: String -> IO (Selenium a -> IO (Either String a)) start url = do host <- getHostName let uri = fromJust (parseURI url) sel = mkSeleniumRCSession host Firefox uri result <- runSelenium sel startSelenium return $ runSelenium (either (\msg -> error msg) id result) ($$) :: forall b t. (Show t) => (Selenium () -> b) -> Selenium t -> b ($$) s c = s $ do r <- c; liftIO (putStrLn $ "Result: " ++ show r); return () -- | Stops a session (in the wrapper returned by start) stop :: Selenium () stop = stopSelenium