diff --git a/bower.json b/bower.json index ed98f16..e88cf23 100644 --- a/bower.json +++ b/bower.json @@ -17,9 +17,8 @@ ], "license": "Apache-2.0", "dependencies": { - "purescript-aff": "^1.1.0", - "purescript-aff-reattempt": "^1.0.0", - "purescript-base": "^1.0.0", - "purescript-dom": "^2.0.0" + "purescript-aff": "^2.0.1", + "purescript-aff-reattempt": "^2.0.0", + "purescript-dom": "^3.1.0" } } diff --git a/package.json b/package.json index 3db909c..d60a96a 100644 --- a/package.json +++ b/package.json @@ -6,13 +6,13 @@ "test": "pulp test" }, "dependencies": { - "chromedriver": "^2.22.0", - "selenium-webdriver": "2.53.2" + "chromedriver": "^2.25.1", + "selenium-webdriver": "3.0.0-beta-3" }, "devDependencies": { "pulp": "^9.0.1", "purescript-psa": "^0.3.9", - "purescript": "^0.9.2", + "purescript": "^0.10.1", "rimraf": "^2.5.4" } } diff --git a/src/Selenium.purs b/src/Selenium.purs index a52cc18..eeac2ca 100644 --- a/src/Selenium.purs +++ b/src/Selenium.purs @@ -52,151 +52,259 @@ module Selenium import Prelude -import Control.Monad.Aff (Aff(), attempt) +import Control.Monad.Aff (Aff, attempt) import Control.Monad.Eff.Exception (error) import Control.Monad.Error.Class (throwError) import Data.Array (uncons) import Data.Either (either) -import Data.Foreign (Foreign()) +import Data.Foreign (Foreign) import Data.Maybe (Maybe(..)) import Data.Tuple (Tuple(..)) import Data.Unfoldable (class Unfoldable, unfoldr) -import Selenium.Types (SELENIUM, Driver, WindowHandle, Location, Window, Size, Element, FileDetector, Locator) +import Selenium.Types + ( SELENIUM + , Driver + , WindowHandle + , Location + , Window + , Size + , Element + , FileDetector + , Locator + ) -- | Go to url -foreign import get :: forall e. Driver -> String -> Aff (selenium :: SELENIUM|e) Unit +foreign import get + ∷ ∀ e + . Driver + → String + → Aff (selenium ∷ SELENIUM|e) Unit + -- | Wait until first argument returns 'true'. If it returns false an error will be raised -foreign import wait :: forall e. Aff (selenium :: SELENIUM|e) Boolean -> - Int -> Driver -> - Aff (selenium :: SELENIUM|e) Unit +foreign import wait + ∷ ∀ e + . Aff (selenium ∷ SELENIUM|e) Boolean + → Int + → Driver + → Aff (selenium ∷ SELENIUM|e) Unit -- | Finalizer -foreign import quit :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit - +foreign import quit + ∷ ∀ e + . Driver + → Aff (selenium ∷ SELENIUM|e) Unit -- LOCATOR BUILDERS -foreign import byClassName :: forall e. String -> Aff (selenium :: SELENIUM|e) Locator -foreign import byCss :: forall e. String -> Aff (selenium :: SELENIUM|e) Locator -foreign import byId :: forall e. String -> Aff (selenium :: SELENIUM|e) Locator -foreign import byName :: forall e. String -> Aff (selenium :: SELENIUM|e) Locator -foreign import byXPath :: forall e. String -> Aff (selenium :: SELENIUM|e) Locator +foreign import byClassName + ∷ ∀ e. String → Aff (selenium ∷ SELENIUM|e) Locator +foreign import byCss + ∷ ∀ e. String → Aff (selenium ∷ SELENIUM|e) Locator +foreign import byId + ∷ ∀ e. String → Aff (selenium ∷ SELENIUM|e) Locator +foreign import byName + ∷ ∀ e. String → Aff (selenium ∷ SELENIUM|e) Locator +foreign import byXPath + ∷ ∀ e. String → Aff (selenium ∷ SELENIUM|e) Locator -- | Build locator from asynchronous function returning element. -- | I.e. this locator will find first visible element with `.common-element` class -- | ```purescript --- | affLocator \el -> do --- | commonElements <- byCss ".common-element" >>= findElements el --- | flagedElements <- traverse (\el -> Tuple el <$> isVisible el) commonElements +-- | affLocator \el → do +-- | commonElements ← byCss ".common-element" >>= findElements el +-- | flagedElements ← traverse (\el → Tuple el <$> isVisible el) commonElements -- | maybe err pure $ foldl foldFn Nothing flagedElements -- | where -- | err = throwError $ error "all common elements are not visible" -- | foldFn Nothing (Tuple el true) = Just el -- | foldFn a _ = a -- | ``` -foreign import affLocator :: forall e. (Element -> Aff (selenium :: SELENIUM|e) Element) -> Aff (selenium :: SELENIUM|e) Locator - -foreign import showLocator :: Locator -> String - -foreign import _findElement :: forall e a. Maybe a -> (a -> Maybe a) -> - Driver -> Locator -> Aff (selenium :: SELENIUM|e) (Maybe Element) -foreign import _findChild :: forall e a. Maybe a -> (a -> Maybe a) -> - Element -> Locator -> Aff (selenium :: SELENIUM|e) (Maybe Element) -foreign import _findElements :: forall e. Driver -> Locator -> Aff (selenium :: SELENIUM|e) (Array Element) -foreign import _findChildren :: forall e. Element -> Locator -> Aff (selenium :: SELENIUM|e) (Array Element) -foreign import findExact :: forall e. Driver -> Locator -> Aff (selenium :: SELENIUM|e) Element -foreign import childExact :: forall e. Element -> Locator -> Aff (selenium :: SELENIUM|e) Element +foreign import affLocator + ∷ ∀ e + . (Element → Aff (selenium ∷ SELENIUM|e) Element) + → Aff (selenium ∷ SELENIUM|e) Locator + +foreign import showLocator + ∷ Locator + → String + +foreign import _findElement + ∷ ∀ e a + . Maybe a + → (a → Maybe a) + → Driver + → Locator + → Aff (selenium ∷ SELENIUM|e) (Maybe Element) + +foreign import _findChild + ∷ ∀ e a + . Maybe a + → (a → Maybe a) + → Element + → Locator + → Aff (selenium ∷ SELENIUM|e) (Maybe Element) + +foreign import _findElements + ∷ ∀ e + . Driver + → Locator + → Aff (selenium ∷ SELENIUM|e) (Array Element) + +foreign import _findChildren + ∷ ∀ e + . Element + → Locator + → Aff (selenium ∷ SELENIUM|e) (Array Element) + +foreign import findExact + ∷ ∀ e + . Driver + → Locator + → Aff (selenium ∷ SELENIUM|e) Element + +foreign import childExact + ∷ ∀ e + . Element + → Locator + → Aff (selenium ∷ SELENIUM|e) Element -- | Tries to find an element starting from `document`; will return `Nothing` if there -- | is no element can be found by locator -findElement :: forall e. Driver -> Locator -> Aff (selenium :: SELENIUM|e) (Maybe Element) -findElement = _findElement Nothing Just +findElement + ∷ ∀ e. Driver → Locator → Aff (selenium ∷ SELENIUM|e) (Maybe Element) +findElement = + _findElement Nothing Just -- | Tries to find element and throws an error if it succeeds. -loseElement :: forall e. Driver -> Locator -> Aff (selenium :: SELENIUM|e) Unit +loseElement + ∷ ∀ e + . Driver + → Locator + → Aff (selenium ∷ SELENIUM|e) Unit loseElement driver locator = do - result <- attempt $ findExact driver locator + result ← attempt $ findExact driver locator either (const $ pure unit) (const $ throwError $ error failMessage) result where failMessage = "Found element with locator: " <> showLocator locator -- | Finds elements by locator from `document` -findElements :: forall e f. (Unfoldable f) => Driver -> Locator -> Aff (selenium :: SELENIUM|e) (f Element) -findElements driver locator = map fromArray $ _findElements driver locator +findElements + ∷ ∀ e f. (Unfoldable f) ⇒ Driver → Locator → Aff (selenium ∷ SELENIUM|e) (f Element) +findElements driver locator = + map fromArray $ _findElements driver locator -- | Same as `findElement` but starts searching from custom element -findChild :: forall e. Element -> Locator -> Aff (selenium :: SELENIUM|e) (Maybe Element) -findChild = _findChild Nothing Just +findChild + ∷ ∀ e. Element → Locator → Aff (selenium ∷ SELENIUM|e) (Maybe Element) +findChild = + _findChild Nothing Just -- | Same as `findElements` but starts searching from custom element -findChildren :: forall e f. (Unfoldable f) => Element -> Locator -> Aff (selenium ::SELENIUM|e) (f Element) -findChildren el locator = map fromArray $ _findChildren el locator - -foreign import setFileDetector :: forall e. Driver -> FileDetector -> Aff (selenium :: SELENIUM|e) Unit - -foreign import navigateBack :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit -foreign import navigateForward :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit -foreign import refresh :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit -foreign import navigateTo :: forall e. String -> Driver -> Aff (selenium :: SELENIUM|e) Unit -foreign import getCurrentUrl :: forall e. Driver -> Aff (selenium :: SELENIUM|e) String -foreign import getTitle :: forall e. Driver -> Aff (selenium :: SELENIUM|e) String +findChildren + ∷ ∀ e f + . (Unfoldable f) + ⇒ Element + → Locator + → Aff (selenium ∷SELENIUM|e) (f Element) +findChildren el locator = + map fromArray $ _findChildren el locator + +foreign import setFileDetector + ∷ ∀ e. Driver → FileDetector → Aff (selenium ∷ SELENIUM|e) Unit +foreign import navigateBack + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Unit +foreign import navigateForward + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Unit +foreign import refresh + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Unit +foreign import navigateTo + ∷ ∀ e. String → Driver → Aff (selenium ∷ SELENIUM|e) Unit +foreign import getCurrentUrl + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) String +foreign import getTitle + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) String -- | Executes javascript script from `String` argument. -foreign import executeStr :: forall e. Driver -> String -> Aff (selenium :: SELENIUM|e) Foreign - -foreign import sendKeysEl :: forall e. String -> Element -> Aff (selenium :: SELENIUM|e) Unit -foreign import clickEl :: forall e. Element -> Aff (selenium :: SELENIUM|e) Unit -foreign import getCssValue :: forall e. Element -> String -> Aff (selenium :: SELENIUM|e) String -foreign import _getAttribute :: forall e a. Maybe a -> (a -> Maybe a) -> - Element -> String -> Aff (selenium :: SELENIUM|e) (Maybe String) +foreign import executeStr + ∷ ∀ e. Driver → String → Aff (selenium ∷ SELENIUM|e) Foreign +foreign import sendKeysEl + ∷ ∀ e. String → Element → Aff (selenium ∷ SELENIUM|e) Unit +foreign import clickEl + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) Unit +foreign import getCssValue + ∷ ∀ e. Element → String → Aff (selenium ∷ SELENIUM|e) String +foreign import _getAttribute + ∷ ∀ e a + . Maybe a + → (a → Maybe a) + → Element + → String + → Aff (selenium ∷ SELENIUM|e) (Maybe String) -- | Tries to find an element starting from `document`; will return `Nothing` if there -- | is no element can be found by locator -getAttribute :: forall e. Element -> String -> Aff (selenium :: SELENIUM|e) (Maybe String) +getAttribute + ∷ ∀ e. Element → String → Aff (selenium ∷ SELENIUM|e) (Maybe String) getAttribute = _getAttribute Nothing Just -foreign import getText :: forall e. Element -> Aff (selenium :: SELENIUM|e) String -foreign import isDisplayed :: forall e. Element -> Aff (selenium :: SELENIUM|e) Boolean -foreign import isEnabled :: forall e. Element -> Aff (selenium :: SELENIUM|e) Boolean -foreign import getInnerHtml :: forall e. Element -> Aff (selenium :: SELENIUM|e) String -foreign import getSize :: forall e. Element -> Aff (selenium :: SELENIUM|e) Size -foreign import getLocation :: forall e. Element -> Aff (selenium :: SELENIUM|e) Location +foreign import getText + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) String +foreign import isDisplayed + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) Boolean +foreign import isEnabled + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) Boolean +foreign import getInnerHtml + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) String +foreign import getSize + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) Size +foreign import getLocation + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) Location -- | Clear `value` of element, if it has no value will do nothing. -- | If `value` is weakly referenced by `virtual-dom` (`purescript-halogen`) -- | will not work -- to clear such inputs one should use direct signal from -- | `Selenium.ActionSequence` -foreign import clearEl :: forall e. Element -> Aff (selenium :: SELENIUM|e) Unit +foreign import clearEl + ∷ ∀ e. Element → Aff (selenium ∷ SELENIUM|e) Unit -- | Returns png base64 encoded png image -foreign import takeScreenshot :: forall e. Driver -> Aff (selenium :: SELENIUM |e) String +foreign import takeScreenshot + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM |e) String -- | Saves screenshot to path -foreign import saveScreenshot :: forall e. String -> Driver -> Aff (selenium :: SELENIUM |e) Unit - -foreign import getWindow :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Window - -foreign import getWindowPosition :: forall e. Window -> Aff (selenium :: SELENIUM|e) Location - -foreign import getWindowSize :: forall e. Window -> Aff (selenium :: SELENIUM|e) Size - -foreign import maximizeWindow :: forall e. Window -> Aff (selenium :: SELENIUM|e) Unit - -foreign import setWindowPosition :: forall e. Location -> Window -> Aff (selenium :: SELENIUM|e) Unit - -foreign import setWindowSize :: forall e. Size -> Window -> Aff (selenium :: SELENIUM|e) Unit - -foreign import getWindowScroll :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Location - -foreign import getWindowHandle :: forall e. Driver -> Aff (selenium :: SELENIUM|e) WindowHandle - -foreign import _getAllWindowHandles :: forall e. Driver -> Aff (selenium :: SELENIUM|e) (Array WindowHandle) - -getAllWindowHandles :: forall f e. (Unfoldable f) => Driver -> Aff (selenium :: SELENIUM |e) (f WindowHandle) -getAllWindowHandles driver = map fromArray $ _getAllWindowHandles driver - - -fromArray :: forall a f. (Unfoldable f) => Array a -> f a -fromArray = unfoldr (\xs -> (\rec -> Tuple rec.head rec.tail) <$> uncons xs) - -foreign import switchTo :: forall e. WindowHandle -> Driver -> Aff (selenium :: SELENIUM |e) Unit - -foreign import close :: forall e. Driver -> Aff (selenium :: SELENIUM |e) Unit +foreign import saveScreenshot + ∷ ∀ e. String → Driver → Aff (selenium ∷ SELENIUM |e) Unit +foreign import getWindow + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Window +foreign import getWindowPosition + ∷ ∀ e. Window → Aff (selenium ∷ SELENIUM|e) Location +foreign import getWindowSize + ∷ ∀ e. Window → Aff (selenium ∷ SELENIUM|e) Size +foreign import maximizeWindow + ∷ ∀ e. Window → Aff (selenium ∷ SELENIUM|e) Unit +foreign import setWindowPosition + ∷ ∀ e. Location → Window → Aff (selenium ∷ SELENIUM|e) Unit +foreign import setWindowSize + ∷ ∀ e. Size → Window → Aff (selenium ∷ SELENIUM|e) Unit +foreign import getWindowScroll + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Location +foreign import getWindowHandle + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) WindowHandle +foreign import _getAllWindowHandles + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) (Array WindowHandle) + +getAllWindowHandles + ∷ ∀ f e + . (Unfoldable f) + ⇒ Driver + → Aff (selenium ∷ SELENIUM |e) (f WindowHandle) +getAllWindowHandles driver = + map fromArray $ _getAllWindowHandles driver + +fromArray + ∷ ∀ a f. (Unfoldable f) ⇒ Array a → f a +fromArray = + unfoldr (\xs → (\rec → Tuple rec.head rec.tail) <$> uncons xs) + +foreign import switchTo + ∷ ∀ e. WindowHandle → Driver → Aff (selenium ∷ SELENIUM |e) Unit +foreign import close + ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM |e) Unit diff --git a/src/Selenium/ActionSequence.purs b/src/Selenium/ActionSequence.purs index fe4d81f..706fc35 100644 --- a/src/Selenium/ActionSequence.purs +++ b/src/Selenium/ActionSequence.purs @@ -44,76 +44,76 @@ data Command newtype Sequence a = Sequence (Writer (List Command) a) -unSequence :: forall a. Sequence a -> Writer (List Command) a +unSequence ∷ ∀ a. Sequence a → Writer (List Command) a unSequence (Sequence a) = a -instance functorSequence :: Functor Sequence where +instance functorSequence ∷ Functor Sequence where map f (Sequence a) = Sequence $ f <$> a -instance applySequence :: Apply Sequence where +instance applySequence ∷ Apply Sequence where apply (Sequence f) (Sequence w) = Sequence $ f <*> w -instance bindSequence :: Bind Sequence where +instance bindSequence ∷ Bind Sequence where bind (Sequence w) f = Sequence $ w >>= unSequence <<< f -instance applicativeSequence :: Applicative Sequence where +instance applicativeSequence ∷ Applicative Sequence where pure = Sequence <<< pure -instance monadSequence :: Monad Sequence +instance monadSequence ∷ Monad Sequence -rule :: Command -> Sequence Unit +rule ∷ Command → Sequence Unit rule = Sequence <<< tell <<< singleton -click :: MouseButton -> Element -> Sequence Unit +click ∷ MouseButton → Element → Sequence Unit click btn el = rule $ Click btn el -leftClick :: Element -> Sequence Unit +leftClick ∷ Element → Sequence Unit leftClick = click leftButton -doubleClick :: MouseButton -> Element -> Sequence Unit +doubleClick ∷ MouseButton → Element → Sequence Unit doubleClick btn el = rule $ DoubleClick btn el -hover :: Element -> Sequence Unit +hover ∷ Element → Sequence Unit hover el = rule $ MouseToElement el -mouseDown :: MouseButton -> Element -> Sequence Unit +mouseDown ∷ MouseButton → Element → Sequence Unit mouseDown btn el = rule $ MouseDown btn el -mouseUp :: MouseButton -> Element -> Sequence Unit +mouseUp ∷ MouseButton → Element → Sequence Unit mouseUp btn el = rule $ MouseUp btn el -sendKeys :: String -> Sequence Unit +sendKeys ∷ String → Sequence Unit sendKeys keys = rule $ SendKeys keys -mouseToLocation :: Location -> Sequence Unit +mouseToLocation ∷ Location → Sequence Unit mouseToLocation loc = rule $ MouseToLocation loc -- | This function is used only with special keys (META, CONTROL, etc) -- | It doesn't emulate __keyDown__ event -keyDown :: ControlKey -> Sequence Unit +keyDown ∷ ControlKey → Sequence Unit keyDown k = rule $ KeyDown k -- | This function is used only with special keys (META, CONTROL, etc) -- | It doesn't emulate __keyUp__ event -keyUp :: ControlKey -> Sequence Unit +keyUp ∷ ControlKey → Sequence Unit keyUp k = rule $ KeyUp k -dndToElement :: Element -> Element -> Sequence Unit +dndToElement ∷ Element → Element → Sequence Unit dndToElement el tgt = rule $ DnDToElement el tgt -dndToLocation :: Element -> Location -> Sequence Unit +dndToLocation ∷ Element → Location → Sequence Unit dndToLocation el tgt = rule $ DnDToLocation el tgt -sequence :: forall e. Driver -> Sequence Unit -> Aff (selenium :: SELENIUM|e) Unit +sequence ∷ ∀ e. Driver → Sequence Unit → Aff (selenium ∷ SELENIUM|e) Unit sequence driver commands = do - seq <- newSequence driver + seq ← newSequence driver performSequence $ interpret (execWriter $ unSequence commands) seq -interpret :: List Command -> ActionSequence -> ActionSequence +interpret ∷ List Command → ActionSequence → ActionSequence interpret commands seq = foldl foldFn seq commands where - foldFn :: ActionSequence -> Command -> ActionSequence + foldFn ∷ ActionSequence → Command → ActionSequence foldFn seq (Click btn el) = runFn3 _click seq btn el foldFn seq (DoubleClick btn el) = runFn3 _doubleClick seq btn el foldFn seq (MouseToElement el) = runFn2 _mouseToElement seq el @@ -127,18 +127,18 @@ interpret commands seq = foldFn seq (DnDToLocation el tgt) = runFn3 _dndToLocation seq el tgt -foreign import newSequence :: forall e. Driver -> Aff (selenium :: SELENIUM|e) ActionSequence +foreign import newSequence ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) ActionSequence -foreign import performSequence :: forall e. ActionSequence -> Aff (selenium :: SELENIUM |e) Unit +foreign import performSequence ∷ ∀ e. ActionSequence → Aff (selenium ∷ SELENIUM |e) Unit -foreign import _click :: Fn3 ActionSequence MouseButton Element ActionSequence -foreign import _doubleClick :: Fn3 ActionSequence MouseButton Element ActionSequence -foreign import _mouseToElement :: Fn2 ActionSequence Element ActionSequence -foreign import _mouseToLocation :: Fn2 ActionSequence Location ActionSequence -foreign import _mouseDown :: Fn3 ActionSequence MouseButton Element ActionSequence -foreign import _mouseUp :: Fn3 ActionSequence MouseButton Element ActionSequence -foreign import _keyDown :: Fn2 ActionSequence ControlKey ActionSequence -foreign import _keyUp :: Fn2 ActionSequence ControlKey ActionSequence -foreign import _sendKeys :: Fn2 ActionSequence String ActionSequence -foreign import _dndToElement :: Fn3 ActionSequence Element Element ActionSequence -foreign import _dndToLocation :: Fn3 ActionSequence Element Location ActionSequence +foreign import _click ∷ Fn3 ActionSequence MouseButton Element ActionSequence +foreign import _doubleClick ∷ Fn3 ActionSequence MouseButton Element ActionSequence +foreign import _mouseToElement ∷ Fn2 ActionSequence Element ActionSequence +foreign import _mouseToLocation ∷ Fn2 ActionSequence Location ActionSequence +foreign import _mouseDown ∷ Fn3 ActionSequence MouseButton Element ActionSequence +foreign import _mouseUp ∷ Fn3 ActionSequence MouseButton Element ActionSequence +foreign import _keyDown ∷ Fn2 ActionSequence ControlKey ActionSequence +foreign import _keyUp ∷ Fn2 ActionSequence ControlKey ActionSequence +foreign import _sendKeys ∷ Fn2 ActionSequence String ActionSequence +foreign import _dndToElement ∷ Fn3 ActionSequence Element Element ActionSequence +foreign import _dndToLocation ∷ Fn3 ActionSequence Element Location ActionSequence diff --git a/src/Selenium/Browser.purs b/src/Selenium/Browser.purs index 8c8fd51..782966a 100644 --- a/src/Selenium/Browser.purs +++ b/src/Selenium/Browser.purs @@ -21,7 +21,7 @@ data Browser | Opera | Safari -browser2str :: Browser -> String +browser2str ∷ Browser → String browser2str PhantomJS = "phantomjs" browser2str Chrome = "chrome" browser2str FireFox = "firefox" @@ -29,7 +29,7 @@ browser2str Opera = "opera" browser2str Safari = "safari" browser2str IE = "ie" -str2browser :: String -> Maybe Browser +str2browser ∷ String → Maybe Browser str2browser "phantomjs" = pure PhantomJS str2browser "chrome" = pure Chrome str2browser "firefox" = pure FireFox @@ -38,10 +38,10 @@ str2browser "opera" = pure Opera str2browser "safari" = pure Safari str2browser _ = Nothing -foreign import _browserCapabilities :: String -> Capabilities +foreign import _browserCapabilities ∷ String → Capabilities -browserCapabilities :: Browser -> Capabilities +browserCapabilities ∷ Browser → Capabilities browserCapabilities = browser2str >>> _browserCapabilities -foreign import versionCapabilities :: String -> Capabilities -foreign import platformCapabilities :: String -> Capabilities +foreign import versionCapabilities ∷ String → Capabilities +foreign import platformCapabilities ∷ String → Capabilities diff --git a/src/Selenium/Builder.purs b/src/Selenium/Builder.purs index 27033ee..a418084 100644 --- a/src/Selenium/Builder.purs +++ b/src/Selenium/Builder.purs @@ -39,66 +39,66 @@ data Command newtype Build a = Build (Writer (Tuple Capabilities (List Command)) a) -unBuild :: forall a. Build a -> Writer (Tuple Capabilities (List Command)) a +unBuild ∷ ∀ a. Build a → Writer (Tuple Capabilities (List Command)) a unBuild (Build a) = a -instance functorBuild :: Functor Build where +instance functorBuild ∷ Functor Build where map f (Build a) = Build $ f <$> a -instance applyBuild :: Apply Build where +instance applyBuild ∷ Apply Build where apply (Build f) (Build w) = Build $ f <*> w -instance bindBuild :: Bind Build where +instance bindBuild ∷ Bind Build where bind (Build w) f = Build $ w >>= unBuild <<< f -instance applicativeBuild :: Applicative Build where +instance applicativeBuild ∷ Applicative Build where pure = Build <<< pure -instance monadBuild :: Monad Build +instance monadBuild ∷ Monad Build -rule :: Command -> Build Unit +rule ∷ Command → Build Unit rule = Build <<< tell <<< Tuple emptyCapabilities <<< singleton -version :: String -> Build Unit +version ∷ String → Build Unit version = withCapabilities <<< versionCapabilities -platform :: String -> Build Unit +platform ∷ String → Build Unit platform = withCapabilities <<< platformCapabilities -usingServer :: String -> Build Unit +usingServer ∷ String → Build Unit usingServer = rule <<< UsingServer -scrollBehaviour :: ScrollBehaviour -> Build Unit +scrollBehaviour ∷ ScrollBehaviour → Build Unit scrollBehaviour = rule <<< SetScrollBehaviour -withCapabilities :: Capabilities -> Build Unit +withCapabilities ∷ Capabilities → Build Unit withCapabilities c = Build $ tell $ Tuple c noRules where - noRules :: List Command + noRules ∷ List Command noRules = Nil -browser :: Browser -> Build Unit +browser ∷ Browser → Build Unit browser = withCapabilities <<< browserCapabilities -build :: forall e. Build Unit -> Aff (selenium :: SELENIUM|e) Driver +build ∷ ∀ e. Build Unit → Aff (selenium ∷ SELENIUM|e) Driver build dsl = do - builder <- _newBuilder + builder ← _newBuilder case execWriter $ unBuild dsl of - Tuple capabilities commands -> + Tuple capabilities commands → _build $ runFn2 _withCapabilities (interpret commands builder) capabilities -interpret :: List Command -> Builder -> Builder +interpret ∷ List Command → Builder → Builder interpret commands b = foldl foldFn b commands where - foldFn :: Builder -> Command -> Builder + foldFn ∷ Builder → Command → Builder foldFn b (UsingServer s) = runFn2 _usingServer b s foldFn b (SetScrollBehaviour bh) = runFn2 _setScrollBehaviour b bh foldFn b _ = b -foreign import _newBuilder :: forall e. Aff (selenium :: SELENIUM|e) Builder -foreign import _build :: forall e. Builder -> Aff (selenium :: SELENIUM|e) Driver +foreign import _newBuilder ∷ ∀ e. Aff (selenium ∷ SELENIUM|e) Builder +foreign import _build ∷ ∀ e. Builder → Aff (selenium ∷ SELENIUM|e) Driver -foreign import _usingServer :: Fn2 Builder String Builder -foreign import _setScrollBehaviour :: Fn2 Builder ScrollBehaviour Builder -foreign import _withCapabilities :: Fn2 Builder Capabilities Builder +foreign import _usingServer ∷ Fn2 Builder String Builder +foreign import _setScrollBehaviour ∷ Fn2 Builder ScrollBehaviour Builder +foreign import _withCapabilities ∷ Fn2 Builder Capabilities Builder diff --git a/src/Selenium/Capabilities.purs b/src/Selenium/Capabilities.purs index f766101..fb3be98 100644 --- a/src/Selenium/Capabilities.purs +++ b/src/Selenium/Capabilities.purs @@ -4,12 +4,12 @@ import Prelude import Data.Monoid (class Monoid) -foreign import data Capabilities :: * -foreign import emptyCapabilities :: Capabilities -foreign import appendCapabilities :: Capabilities -> Capabilities -> Capabilities +foreign import data Capabilities ∷ * +foreign import emptyCapabilities ∷ Capabilities +foreign import appendCapabilities ∷ Capabilities → Capabilities → Capabilities -instance semigroupCapabilities :: Semigroup Capabilities where +instance semigroupCapabilities ∷ Semigroup Capabilities where append = appendCapabilities -instance monoidCapabilities :: Monoid Capabilities where +instance monoidCapabilities ∷ Monoid Capabilities where mempty = emptyCapabilities diff --git a/src/Selenium/Combinators.purs b/src/Selenium/Combinators.purs index bcb4646..dcc8537 100644 --- a/src/Selenium/Combinators.purs +++ b/src/Selenium/Combinators.purs @@ -5,7 +5,7 @@ import Prelude import Control.Alt ((<|>)) import Control.Monad.Eff.Exception (error) import Control.Monad.Error.Class (throwError) -import Control.Monad.Trans (lift) +import Control.Monad.Trans.Class (lift) import Data.Either (Either(..), either) import Data.Maybe (Maybe, isJust, maybe) @@ -14,17 +14,17 @@ import Selenium.Monad (Selenium, getCurrentUrl, wait, attempt, findExact, tryRep import Selenium.Types (Element, Locator) -- | Retry computation until it successed but not more then `n` times -retry :: forall e o a. Int -> Selenium e o a -> Selenium e o a +retry ∷ ∀ e o a. Int → Selenium e o a → Selenium e o a retry n action = do - res <- attempt action + res ← attempt action case res of - Left e -> if n > one - then retry (n - one) action - else lift $ throwError $ error "To many retries" - Right r -> pure r + Left e + | n > one → retry (n - one) action + | otherwise → lift $ throwError $ error "To many retries" + Right r → pure r -- | Tries to find element by string checks: css, xpath, id, name and classname -tryFind :: forall e o. String -> Selenium e o Element +tryFind ∷ ∀ e o. String → Selenium e o Element tryFind probablyLocator = (byCss probablyLocator >>= findExact) <|> (byXPath probablyLocator >>= findExact) <|> @@ -32,55 +32,54 @@ tryFind probablyLocator = (byName probablyLocator >>= findExact) <|> (byClassName probablyLocator >>= findExact) -waitUntilJust :: forall e o a. Selenium e o (Maybe a) -> Int -> Selenium e o a +waitUntilJust ∷ ∀ e o a. Selenium e o (Maybe a) → Int → Selenium e o a waitUntilJust check time = do wait (checker $ isJust <$> check) time check >>= maybe (throwError $ error $ "Maybe was not Just after waiting for isJust") pure -- Tries to evaluate `Selenium` if it returns `false` after 500ms -checker :: forall e o. Selenium e o Boolean -> Selenium e o Boolean -checker check = do - res <- check - if res +checker ∷ ∀ e o. Selenium e o Boolean → Selenium e o Boolean +checker check = + check >>= if _ then pure true else later 500 $ checker check -getElementByCss :: forall e o. String -> Selenium e o Element +getElementByCss ∷ ∀ e o. String → Selenium e o Element getElementByCss cls = byCss cls >>= findElement >>= maybe (throwError $ error $ "There is no element matching css: " <> cls) pure -checkNotExistsByCss :: forall e o. String -> Selenium e o Unit +checkNotExistsByCss ∷ ∀ e o. String → Selenium e o Unit checkNotExistsByCss = contra <<< getElementByCss -contra :: forall e o a. Selenium e o a -> Selenium e o Unit +contra ∷ ∀ e o a. Selenium e o a → Selenium e o Unit contra check = do - eR <- attempt check + eR ← attempt check either (const $ pure unit) (const $ throwError $ error "check successed in contra") eR -- | Repeatedly attempts to find an element using the provided selector until the -- | provided timeout elapses. -tryToFind' :: forall e o. Int -> Selenium e o Locator -> Selenium e o Element +tryToFind' ∷ ∀ e o. Int → Selenium e o Locator → Selenium e o Element tryToFind' timeout locator = tryRepeatedlyTo' timeout $ locator >>= findExact -- | Repeatedly tries to find an element using the provided selector until -- | the provided `Selenium`'s `defaultTimeout` elapses. -tryToFind :: forall e o. Selenium e o Locator -> Selenium e o Element +tryToFind ∷ ∀ e o. Selenium e o Locator → Selenium e o Element tryToFind locator = tryRepeatedlyTo $ locator >>= findExact -- | Repeatedly tries to evaluate check (third arg) for timeout ms (first arg) -- | finishes when check evaluates to true. -- | If there is an error during check or it constantly returns `false` -- | throws error with message (second arg) -await :: forall e o. Int -> Selenium e o Boolean -> Selenium e o Unit +await ∷ ∀ e o. Int → Selenium e o Boolean → Selenium e o Unit await timeout check = do - ei <- attempt $ wait (checker check) timeout + ei ← attempt $ wait (checker check) timeout case ei of - Left _ -> throwError $ error "await has no success" - Right _ -> pure unit + Left _ → throwError $ error "await has no success" + Right _ → pure unit -awaitUrlChanged :: forall e o. String -> Selenium e o Boolean +awaitUrlChanged ∷ ∀ e o. String → Selenium e o Boolean awaitUrlChanged oldURL = checker $ (oldURL /= _) <$> getCurrentUrl diff --git a/src/Selenium/FFProfile.purs b/src/Selenium/FFProfile.purs index 18fc5bd..997bbe8 100644 --- a/src/Selenium/FFProfile.purs +++ b/src/Selenium/FFProfile.purs @@ -28,77 +28,77 @@ import Selenium.Types (SELENIUM) import Unsafe.Coerce (unsafeCoerce) -foreign import data FFProfile :: * -foreign import data FFPreference :: * +foreign import data FFProfile ∷ * +foreign import data FFPreference ∷ * data Command = SetPreference String FFPreference newtype FFProfileBuild a = FFProfileBuild (Writer (List Command) a) -unFFProfileBuild :: forall a. FFProfileBuild a -> Writer (List Command) a +unFFProfileBuild ∷ ∀ a. FFProfileBuild a → Writer (List Command) a unFFProfileBuild (FFProfileBuild a) = a -instance functorFFProfileBuild :: Functor FFProfileBuild where +instance functorFFProfileBuild ∷ Functor FFProfileBuild where map f (FFProfileBuild a) = FFProfileBuild $ f <$> a -instance applyFFProfileBuild :: Apply FFProfileBuild where +instance applyFFProfileBuild ∷ Apply FFProfileBuild where apply (FFProfileBuild f) (FFProfileBuild w) = FFProfileBuild $ f <*> w -instance bindFFProfileBuild :: Bind FFProfileBuild where +instance bindFFProfileBuild ∷ Bind FFProfileBuild where bind (FFProfileBuild w) f = FFProfileBuild $ w >>= unFFProfileBuild <<< f -instance applicativeFFProfileBuild :: Applicative FFProfileBuild where +instance applicativeFFProfileBuild ∷ Applicative FFProfileBuild where pure = FFProfileBuild <<< pure -instance monadFFProfileBuild :: Monad FFProfileBuild +instance monadFFProfileBuild ∷ Monad FFProfileBuild -rule :: Command -> FFProfileBuild Unit +rule ∷ Command → FFProfileBuild Unit rule = FFProfileBuild <<< tell <<< singleton -setPreference :: String -> FFPreference -> FFProfileBuild Unit +setPreference ∷ String → FFPreference → FFProfileBuild Unit setPreference key val = rule $ SetPreference key val -setStringPreference :: String -> String -> FFProfileBuild Unit +setStringPreference ∷ String → String → FFProfileBuild Unit setStringPreference key = setPreference key <<< stringToFFPreference -setIntPreference :: String -> Int -> FFProfileBuild Unit +setIntPreference ∷ String → Int → FFProfileBuild Unit setIntPreference key = setPreference key <<< intToFFPreference -setNumberPreference :: String -> Number -> FFProfileBuild Unit +setNumberPreference ∷ String → Number → FFProfileBuild Unit setNumberPreference key = setPreference key <<< numberToFFPreference -setBoolPreference :: String -> Boolean -> FFProfileBuild Unit +setBoolPreference ∷ String → Boolean → FFProfileBuild Unit setBoolPreference key = setPreference key <<< boolToFFPreference -buildFFProfile :: forall e. FFProfileBuild Unit -> Aff (selenium :: SELENIUM|e) Capabilities +buildFFProfile ∷ ∀ e. FFProfileBuild Unit → Aff (selenium ∷ SELENIUM|e) Capabilities buildFFProfile commands = do - profile <- interpret (execWriter $ unFFProfileBuild commands) <$> _newFFProfile + profile ← interpret (execWriter $ unFFProfileBuild commands) <$> _newFFProfile _encode profile -interpret :: List Command -> FFProfile-> FFProfile +interpret ∷ List Command → FFProfile→ FFProfile interpret commands b = foldl foldFn b commands where - foldFn :: FFProfile -> Command -> FFProfile + foldFn ∷ FFProfile → Command → FFProfile foldFn p (SetPreference k v) = _setFFPreference k v p -foreign import _setFFPreference :: String -> FFPreference -> FFProfile -> FFProfile -foreign import _newFFProfile :: forall e. Aff (selenium :: SELENIUM|e) FFProfile -foreign import _encode :: forall e. FFProfile -> Aff (selenium :: SELENIUM|e) Capabilities +foreign import _setFFPreference ∷ String → FFPreference → FFProfile → FFProfile +foreign import _newFFProfile ∷ ∀ e. Aff (selenium ∷ SELENIUM|e) FFProfile +foreign import _encode ∷ ∀ e. FFProfile → Aff (selenium ∷ SELENIUM|e) Capabilities -intToFFPreference :: Int -> FFPreference +intToFFPreference ∷ Int → FFPreference intToFFPreference = unsafeCoerce -numberToFFPreference :: Number -> FFPreference +numberToFFPreference ∷ Number → FFPreference numberToFFPreference = unsafeCoerce -stringToFFPreference :: String -> FFPreference +stringToFFPreference ∷ String → FFPreference stringToFFPreference = unsafeCoerce -boolToFFPreference :: Boolean -> FFPreference +boolToFFPreference ∷ Boolean → FFPreference boolToFFPreference = unsafeCoerce -foreignToFFPreference :: Foreign -> FFPreference +foreignToFFPreference ∷ Foreign → FFPreference foreignToFFPreference = unsafeCoerce diff --git a/src/Selenium/Key.purs b/src/Selenium/Key.purs index b8cf598..1392c00 100644 --- a/src/Selenium/Key.purs +++ b/src/Selenium/Key.purs @@ -3,8 +3,8 @@ module Selenium.Key where import Selenium.Types -- TODO: port all `Key` enum -foreign import altKey :: ControlKey -foreign import controlKey :: ControlKey -foreign import shiftKey :: ControlKey -foreign import commandKey :: ControlKey -foreign import metaKey :: ControlKey +foreign import altKey ∷ ControlKey +foreign import controlKey ∷ ControlKey +foreign import shiftKey ∷ ControlKey +foreign import commandKey ∷ ControlKey +foreign import metaKey ∷ ControlKey diff --git a/src/Selenium/Monad.purs b/src/Selenium/Monad.purs index 81e75e9..3963591 100644 --- a/src/Selenium/Monad.purs +++ b/src/Selenium/Monad.purs @@ -21,7 +21,18 @@ import DOM (DOM) import Selenium as S import Selenium.ActionSequence as AS -import Selenium.Types (WindowHandle, XHRStats, Element, Locator, Driver, FileDetector, Location, Size, Window, SELENIUM) +import Selenium.Types + ( WindowHandle + , XHRStats + , Element + , Locator + , Driver + , FileDetector + , Location + , Size + , Window + , SELENIUM + ) import Selenium.XHR as XHR -- | `Driver` is field of `ReaderT` context @@ -29,228 +40,231 @@ import Selenium.XHR as XHR -- | timeouts) all those configs can be putted to `Selenium e o a` type Selenium e o = ReaderT - {driver :: Driver, defaultTimeout :: Int |o} - (A.Aff (console :: CONSOLE, selenium :: SELENIUM, dom :: DOM, ref :: REF |e)) + {driver ∷ Driver, defaultTimeout ∷ Int |o} + (A.Aff (console ∷ CONSOLE, selenium ∷ SELENIUM, dom ∷ DOM, ref ∷ REF |e)) -- | get driver from context -getDriver :: forall e o. Selenium e o Driver +getDriver ∷ ∀ e o. Selenium e o Driver getDriver = _.driver <$> ask -getWindow :: forall e o. Selenium e o Window +getWindow ∷ ∀ e o. Selenium e o Window getWindow = getDriver >>= lift <<< S.getWindow -getWindowPosition :: forall e o. Selenium e o Location +getWindowPosition ∷ ∀ e o. Selenium e o Location getWindowPosition = getWindow >>= lift <<< S.getWindowPosition -getWindowSize :: forall e o. Selenium e o Size +getWindowSize ∷ ∀ e o. Selenium e o Size getWindowSize = getWindow >>= lift <<< S.getWindowSize -maximizeWindow :: forall e o. Selenium e o Unit +maximizeWindow ∷ ∀ e o. Selenium e o Unit maximizeWindow = getWindow >>= lift <<< S.maximizeWindow -setWindowPosition :: forall e o. Location -> Selenium e o Unit +setWindowPosition ∷ ∀ e o. Location → Selenium e o Unit setWindowPosition pos = getWindow >>= S.setWindowPosition pos >>> lift -setWindowSize :: forall e o. Size -> Selenium e o Unit +setWindowSize ∷ ∀ e o. Size → Selenium e o Unit setWindowSize size = getWindow >>= S.setWindowSize size >>> lift -getWindowScroll :: forall e o. Selenium e o Location +getWindowScroll ∷ ∀ e o. Selenium e o Location getWindowScroll = getDriver >>= S.getWindowScroll >>> lift -- LIFT `Aff` combinators to `Selenium.Monad` -apathize :: forall e o a. Selenium e o a -> Selenium e o Unit -apathize check = ReaderT \r -> +apathize ∷ ∀ e o a. Selenium e o a → Selenium e o Unit +apathize check = ReaderT \r → A.apathize $ runReaderT check r -attempt :: forall e o a. Selenium e o a -> Selenium e o (Either Error a) -attempt check = ReaderT \r -> +attempt ∷ ∀ e o a. Selenium e o a → Selenium e o (Either Error a) +attempt check = ReaderT \r → A.attempt $ runReaderT check r -later :: forall e o a. Int -> Selenium e o a -> Selenium e o a -later time check = ReaderT \r -> +later ∷ ∀ e o a. Int → Selenium e o a → Selenium e o a +later time check = ReaderT \r → A.later' time $ runReaderT check r -- LIFT `Selenium` funcs to `Selenium.Monad` -get :: forall e o. String -> Selenium e o Unit +get ∷ ∀ e o. String → Selenium e o Unit get url = getDriver >>= lift <<< flip S.get url -wait :: forall e o. Selenium e o Boolean -> Int -> Selenium e o Unit -wait check time = ReaderT \r -> +wait ∷ ∀ e o. Selenium e o Boolean → Int → Selenium e o Unit +wait check time = ReaderT \r → S.wait (runReaderT check r) time r.driver -- | Tries the provided Selenium computation repeatedly until the provided timeout expires -tryRepeatedlyTo' :: forall a e o. Int -> Selenium e o a -> Selenium e o a -tryRepeatedlyTo' time selenium = ReaderT \r -> +tryRepeatedlyTo' ∷ ∀ a e o. Int → Selenium e o a → Selenium e o a +tryRepeatedlyTo' time selenium = ReaderT \r → reattempt time (runReaderT selenium r) -- | Tries the provided Selenium computation repeatedly until `Selenium`'s defaultTimeout expires -tryRepeatedlyTo :: forall a e o. Selenium e o a -> Selenium e o a -tryRepeatedlyTo selenium = ask >>= \r -> tryRepeatedlyTo' r.defaultTimeout selenium +tryRepeatedlyTo ∷ ∀ a e o. Selenium e o a → Selenium e o a +tryRepeatedlyTo selenium = ask >>= \r → tryRepeatedlyTo' r.defaultTimeout selenium -byCss :: forall e o. String -> Selenium e o Locator +byCss ∷ ∀ e o. String → Selenium e o Locator byCss = lift <<< S.byCss -byXPath :: forall e o. String -> Selenium e o Locator +byXPath ∷ ∀ e o. String → Selenium e o Locator byXPath = lift <<< S.byXPath -byId :: forall e o. String -> Selenium e o Locator +byId ∷ ∀ e o. String → Selenium e o Locator byId = lift <<< S.byId -byName :: forall e o. String -> Selenium e o Locator +byName ∷ ∀ e o. String → Selenium e o Locator byName = lift <<< S.byName -byClassName :: forall e o. String -> Selenium e o Locator +byClassName ∷ ∀ e o. String → Selenium e o Locator byClassName = lift <<< S.byClassName -- | get element by action returning an element -- | ```purescript --- | locator \el -> do --- | commonElements <- byCss ".common-element" >>= findElements el --- | flaggedElements <- traverse (\el -> Tuple el <$> isVisible el) commonElements +-- | locator \el → do +-- | commonElements ← byCss ".common-element" >>= findElements el +-- | flaggedElements ← traverse (\el → Tuple el <$> isVisible el) commonElements -- | maybe err pure $ foldl foldFn Nothing flaggedElements -- | where -- | err = throwError $ error "all common elements are not visible" -- | foldFn Nothing (Tuple el true) = Just el -- | foldFn a _ = a -- | ``` -locator :: forall e o. (Element -> Selenium e o Element) -> Selenium e o Locator -locator checkFn = ReaderT \r -> - S.affLocator (\el -> runReaderT (checkFn el) r) +locator ∷ ∀ e o. (Element → Selenium e o Element) → Selenium e o Locator +locator checkFn = ReaderT \r → + S.affLocator (\el → runReaderT (checkFn el) r) -- | Tries to find element and return it wrapped in `Just` -findElement :: forall e o. Locator -> Selenium e o (Maybe Element) +findElement ∷ ∀ e o. Locator → Selenium e o (Maybe Element) findElement l = getDriver >>= lift <<< flip S.findElement l -findElements :: forall e o. Locator -> Selenium e o (List Element) +findElements ∷ ∀ e o. Locator → Selenium e o (List Element) findElements l = getDriver >>= lift <<< flip S.findElements l -- | Tries to find child and return it wrapped in `Just` -findChild :: forall e o. Element -> Locator -> Selenium e o (Maybe Element) +findChild ∷ ∀ e o. Element → Locator → Selenium e o (Maybe Element) findChild el loc = lift $ S.findChild el loc -findChildren :: forall e o. Element -> Locator -> Selenium e o (List Element) +findChildren ∷ ∀ e o. Element → Locator → Selenium e o (List Element) findChildren el loc = lift $ S.findChildren el loc -getInnerHtml :: forall e o. Element -> Selenium e o String +getInnerHtml ∷ ∀ e o. Element → Selenium e o String getInnerHtml = lift <<< S.getInnerHtml -getSize :: forall e o. Element -> Selenium e o Size +getSize ∷ ∀ e o. Element → Selenium e o Size getSize = lift <<< S.getSize -getLocation :: forall e o. Element -> Selenium e o Location +getLocation ∷ ∀ e o. Element → Selenium e o Location getLocation = lift <<< S.getLocation -isDisplayed :: forall e o. Element -> Selenium e o Boolean +isDisplayed ∷ ∀ e o. Element → Selenium e o Boolean isDisplayed = lift <<< S.isDisplayed -isEnabled :: forall e o. Element -> Selenium e o Boolean +isEnabled ∷ ∀ e o. Element → Selenium e o Boolean isEnabled = lift <<< S.isEnabled -getCssValue :: forall e o. Element -> String -> Selenium e o String +getCssValue ∷ ∀ e o. Element → String → Selenium e o String getCssValue el key = lift $ S.getCssValue el key -getAttribute :: forall e o. Element -> String -> Selenium e o (Maybe String) +getAttribute ∷ ∀ e o. Element → String → Selenium e o (Maybe String) getAttribute el attr = lift $ S.getAttribute el attr -getText :: forall e o. Element -> Selenium e o String +getText ∷ ∀ e o. Element → Selenium e o String getText el = lift $ S.getText el -clearEl :: forall e o. Element -> Selenium e o Unit +clearEl ∷ ∀ e o. Element → Selenium e o Unit clearEl = lift <<< S.clearEl -clickEl :: forall e o. Element -> Selenium e o Unit +clickEl ∷ ∀ e o. Element → Selenium e o Unit clickEl = lift <<< S.clickEl -sendKeysEl :: forall e o. String -> Element -> Selenium e o Unit +sendKeysEl ∷ ∀ e o. String → Element → Selenium e o Unit sendKeysEl ks el = lift $ S.sendKeysEl ks el -script :: forall e o. String -> Selenium e o Foreign +script ∷ ∀ e o. String → Selenium e o Foreign script str = getDriver >>= flip S.executeStr str >>> lift -getCurrentUrl :: forall e o. Selenium e o String +getCurrentUrl ∷ ∀ e o. Selenium e o String getCurrentUrl = getDriver >>= S.getCurrentUrl >>> lift -navigateBack :: forall e o. Selenium e o Unit +navigateBack ∷ ∀ e o. Selenium e o Unit navigateBack = getDriver >>= S.navigateBack >>> lift -navigateForward :: forall e o. Selenium e o Unit +navigateForward ∷ ∀ e o. Selenium e o Unit navigateForward = getDriver >>= S.navigateForward >>> lift -navigateTo :: forall e o. String -> Selenium e o Unit +navigateTo ∷ ∀ e o. String → Selenium e o Unit navigateTo url = getDriver >>= S.navigateTo url >>> lift -setFileDetector :: forall e o. FileDetector -> Selenium e o Unit +setFileDetector ∷ ∀ e o. FileDetector → Selenium e o Unit setFileDetector fd = getDriver >>= flip S.setFileDetector fd >>> lift -getTitle :: forall e o. Selenium e o String +getTitle ∷ ∀ e o. Selenium e o String getTitle = getDriver >>= S.getTitle >>> lift -- | Run sequence of actions -sequence :: forall e o. AS.Sequence Unit -> Selenium e o Unit +sequence ∷ ∀ e o. AS.Sequence Unit → Selenium e o Unit sequence seq = do getDriver >>= lift <<< flip AS.sequence seq -- | Same as `sequence` but takes function of `ReaderT` as an argument -actions :: forall e o. ({driver :: Driver, defaultTimeout :: Int |o} -> AS.Sequence Unit) -> Selenium e o Unit +actions + ∷ ∀ e o + . ({driver ∷ Driver, defaultTimeout ∷ Int |o} → AS.Sequence Unit) + → Selenium e o Unit actions seqFn = do - ctx <- ask + ctx ← ask sequence $ seqFn ctx -- | Stop computations -stop :: forall e o. Selenium e o Unit +stop ∷ ∀ e o. Selenium e o Unit stop = wait (later top $ pure false) top -refresh :: forall e o. Selenium e o Unit +refresh ∷ ∀ e o. Selenium e o Unit refresh = getDriver >>= S.refresh >>> lift -quit :: forall e o. Selenium e o Unit +quit ∷ ∀ e o. Selenium e o Unit quit = getDriver >>= S.quit >>> lift -takeScreenshot :: forall e o. Selenium e o String +takeScreenshot ∷ ∀ e o. Selenium e o String takeScreenshot = getDriver >>= S.takeScreenshot >>> lift -saveScreenshot :: forall e o. String -> Selenium e o Unit +saveScreenshot ∷ ∀ e o. String → Selenium e o Unit saveScreenshot name = getDriver >>= S.saveScreenshot name >>> lift -- | Tries to find element, if has no success throws an error -findExact :: forall e o. Locator -> Selenium e o Element +findExact ∷ ∀ e o. Locator → Selenium e o Element findExact loc = getDriver >>= flip S.findExact loc >>> lift -- | Tries to find element and throws an error if it succeeds. -loseElement :: forall e o. Locator -> Selenium e o Unit +loseElement ∷ ∀ e o. Locator → Selenium e o Unit loseElement loc = getDriver >>= flip S.loseElement loc >>> lift -- | Tries to find child, if has no success throws an error -childExact :: forall e o. Element -> Locator -> Selenium e o Element +childExact ∷ ∀ e o. Element → Locator → Selenium e o Element childExact el loc = lift $ S.childExact el loc -startSpying :: forall e o. Selenium e o Unit +startSpying ∷ ∀ e o. Selenium e o Unit startSpying = getDriver >>= XHR.startSpying >>> lift -stopSpying :: forall e o. Selenium e o Unit +stopSpying ∷ ∀ e o. Selenium e o Unit stopSpying = getDriver >>= XHR.stopSpying >>> lift -clearLog :: forall e o. Selenium e o Unit +clearLog ∷ ∀ e o. Selenium e o Unit clearLog = getDriver >>= XHR.clearLog >>> lift -getXHRStats :: forall e o. Selenium e o (List XHRStats) +getXHRStats ∷ ∀ e o. Selenium e o (List XHRStats) getXHRStats = getDriver >>= XHR.getStats >>> map fromFoldable >>> lift -getWindowHandle :: forall e o. Selenium e o WindowHandle +getWindowHandle ∷ ∀ e o. Selenium e o WindowHandle getWindowHandle = getDriver >>= S.getWindowHandle >>> lift -getAllWindowHandles :: forall e o. Selenium e o (List WindowHandle) +getAllWindowHandles ∷ ∀ e o. Selenium e o (List WindowHandle) getAllWindowHandles = getDriver >>= S.getAllWindowHandles >>> lift -switchTo :: forall e o. WindowHandle -> Selenium e o Unit +switchTo ∷ ∀ e o. WindowHandle → Selenium e o Unit switchTo w = getDriver >>= S.switchTo w >>> lift -closeWindow :: forall e o. Selenium e o Unit +closeWindow ∷ ∀ e o. Selenium e o Unit closeWindow = getDriver >>= S.close >>> lift diff --git a/src/Selenium/MouseButton.purs b/src/Selenium/MouseButton.purs index 2290281..5cbb299 100644 --- a/src/Selenium/MouseButton.purs +++ b/src/Selenium/MouseButton.purs @@ -2,6 +2,6 @@ module Selenium.MouseButton where import Selenium.Types -foreign import leftButton :: MouseButton -foreign import rightButton :: MouseButton -foreign import middleButton :: MouseButton +foreign import leftButton ∷ MouseButton +foreign import rightButton ∷ MouseButton +foreign import middleButton ∷ MouseButton diff --git a/src/Selenium/Remote.purs b/src/Selenium/Remote.purs index df47829..0681ca4 100644 --- a/src/Selenium/Remote.purs +++ b/src/Selenium/Remote.purs @@ -3,4 +3,4 @@ module Selenium.Remote where import Control.Monad.Eff (Eff) import Selenium.Types -foreign import fileDetector :: forall e. Eff (selenium :: SELENIUM | e) FileDetector +foreign import fileDetector ∷ ∀ e. Eff (selenium ∷ SELENIUM | e) FileDetector diff --git a/src/Selenium/ScrollBehaviour.purs b/src/Selenium/ScrollBehaviour.purs index b4b467f..25d77b0 100644 --- a/src/Selenium/ScrollBehaviour.purs +++ b/src/Selenium/ScrollBehaviour.purs @@ -2,5 +2,5 @@ module Selenium.ScrollBehaviour where import Selenium.Types -foreign import top :: ScrollBehaviour -foreign import bottom :: ScrollBehaviour +foreign import top ∷ ScrollBehaviour +foreign import bottom ∷ ScrollBehaviour diff --git a/src/Selenium/Types.purs b/src/Selenium/Types.purs index b216913..f46102e 100644 --- a/src/Selenium/Types.purs +++ b/src/Selenium/Types.purs @@ -2,32 +2,34 @@ module Selenium.Types where import Prelude -import Data.Either (Either(..)) +import Control.Monad.Error.Class (throwError) + import Data.Foreign (readString, ForeignError(..)) import Data.Foreign.Class (class IsForeign) import Data.Maybe (Maybe) +import Data.List.NonEmpty as NEL import Data.String (toLower) -foreign import data Builder :: * -foreign import data SELENIUM :: ! -foreign import data Driver :: * -foreign import data Window :: * -foreign import data Until :: * -foreign import data Element :: * -foreign import data Locator :: * -foreign import data ActionSequence :: * -foreign import data MouseButton :: * -foreign import data ChromeOptions :: * -foreign import data ControlFlow :: * -foreign import data FirefoxOptions :: * -foreign import data IEOptions :: * -foreign import data LoggingPrefs :: * -foreign import data OperaOptions :: * -foreign import data ProxyConfig :: * -foreign import data SafariOptions :: * -foreign import data ScrollBehaviour :: * -foreign import data FileDetector :: * -foreign import data WindowHandle :: * +foreign import data Builder ∷ * +foreign import data SELENIUM ∷ ! +foreign import data Driver ∷ * +foreign import data Window ∷ * +foreign import data Until ∷ * +foreign import data Element ∷ * +foreign import data Locator ∷ * +foreign import data ActionSequence ∷ * +foreign import data MouseButton ∷ * +foreign import data ChromeOptions ∷ * +foreign import data ControlFlow ∷ * +foreign import data FirefoxOptions ∷ * +foreign import data IEOptions ∷ * +foreign import data LoggingPrefs ∷ * +foreign import data OperaOptions ∷ * +foreign import data ProxyConfig ∷ * +foreign import data SafariOptions ∷ * +foreign import data ScrollBehaviour ∷ * +foreign import data FileDetector ∷ * +foreign import data WindowHandle ∷ * -- | Copied from `purescript-affjax` because the only thing we -- | need from `affjax` is `Method` @@ -43,7 +45,9 @@ data Method | COPY | CustomMethod String -instance eqMethod :: Eq Method where +derive instance eqMethod ∷ Eq Method +{- +instance eqMethod ∷ Eq Method where eq DELETE DELETE = true eq GET GET = true eq HEAD HEAD = true @@ -55,62 +59,57 @@ instance eqMethod :: Eq Method where eq COPY COPY = true eq (CustomMethod a) (CustomMethod b) = a == b eq _ _ = false +-} - -instance methodIsForeign :: IsForeign Method where +instance methodIsForeign ∷ IsForeign Method where read f = do - str <- readString f + str ← readString f pure $ case toLower str of - "delete" -> DELETE - "get" -> GET - "head" -> HEAD - "options" -> OPTIONS - "patch" -> PATCH - "post" -> POST - "put" -> PUT - "move" -> MOVE - "copy" -> COPY - a -> CustomMethod a + "delete" → DELETE + "get" → GET + "head" → HEAD + "options" → OPTIONS + "patch" → PATCH + "post" → POST + "put" → PUT + "move" → MOVE + "copy" → COPY + a → CustomMethod a data XHRState = Stale | Opened | Loaded -instance xhrStateEq :: Eq XHRState where - eq Stale Stale = true - eq Opened Opened = true - eq Loaded Loaded = true - eq _ _ = false +derive instance eqXHRState ∷ Eq XHRState -instance xhrStateIsForeign :: IsForeign XHRState where +instance xhrStateIsForeign ∷ IsForeign XHRState where read f = do - str <- readString f + str ← readString f case str of - "stale" -> pure Stale - "opened" -> pure Opened - "loaded" -> pure Loaded - _ -> Left $ TypeMismatch "xhr state" "string" - + "stale" → pure Stale + "opened" → pure Opened + "loaded" → pure Loaded + _ → throwError $ NEL.singleton $ TypeMismatch "xhr state" "string" type Location = - { x :: Int - , y :: Int + { x ∷ Int + , y ∷ Int } type Size = - { width :: Int - , height :: Int + { width ∷ Int + , height ∷ Int } newtype ControlKey = ControlKey String type XHRStats = - { method :: Method - , url :: String - , async :: Boolean - , user :: Maybe String - , password :: Maybe String - , state :: XHRState + { method ∷ Method + , url ∷ String + , async ∷ Boolean + , user ∷ Maybe String + , password ∷ Maybe String + , state ∷ XHRState } diff --git a/src/Selenium/XHR.purs b/src/Selenium/XHR.purs index 57072ce..edaf318 100644 --- a/src/Selenium/XHR.purs +++ b/src/Selenium/XHR.purs @@ -2,9 +2,10 @@ module Selenium.XHR where import Prelude -import Control.Monad.Aff (Aff()) +import Control.Monad.Aff (Aff) import Control.Monad.Eff.Exception (error) import Control.Monad.Error.Class (throwError) +import Control.Monad.Except (runExcept) import Data.Either (either, Either(..)) import Data.Foreign (readBoolean, isUndefined, readArray) @@ -17,7 +18,7 @@ import Selenium.Types (XHRStats, SELENIUM, Driver) -- | Start spy on xhrs. It defines global variable in browser -- | and put information about to it. -startSpying :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit +startSpying ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Unit startSpying driver = void $ executeStr driver """ "use strict" @@ -101,7 +102,7 @@ if (window.__SELENIUM__) { """ -- | Return xhr's method to initial. Will not raise an error if hasn't been initiated -stopSpying :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit +stopSpying ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Unit stopSpying driver = void $ executeStr driver """ if (window.__SELENIUM__) { window.__SELENIUM__.unspy(); @@ -109,9 +110,9 @@ if (window.__SELENIUM__) { """ -- | Clean log. Will raise an error if spying hasn't been initiated -clearLog :: forall e. Driver -> Aff (selenium :: SELENIUM|e) Unit +clearLog ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) Unit clearLog driver = do - success <- executeStr driver """ + success ← executeStr driver """ if (!window.__SELENIUM__) { return false; } @@ -120,14 +121,14 @@ clearLog driver = do return true; } """ - case readBoolean success of - Right true -> pure unit - _ -> throwError $ error "spying is inactive" + case runExcept $ readBoolean success of + Right true → pure unit + _ → throwError $ error "spying is inactive" -- | Get recorded xhr stats. If spying has not been set will raise an error -getStats :: forall e. Driver -> Aff (selenium :: SELENIUM|e) (Array XHRStats) +getStats ∷ ∀ e. Driver → Aff (selenium ∷ SELENIUM|e) (Array XHRStats) getStats driver = do - log <- executeStr driver """ + log ← executeStr driver """ if (!window.__SELENIUM__) { return undefined; } @@ -135,18 +136,18 @@ getStats driver = do return window.__SELENIUM__.log; } """ - if isUndefined log - then throwError $ error "spying is inactive" - else pure unit - either (const $ throwError $ error "incorrect log") pure do - arr <- readArray log - for arr \el -> do - state <- readProp "state" el - method <- readProp "method" el - url <- readProp "url" el - async <- readProp "async" el - password <- unNullOrUndefined <$> readProp "password" el - user <- unNullOrUndefined <$> readProp "user" el + when (isUndefined log) + $ throwError $ error "spying is inactive" + + either (const $ throwError $ error "incorrect log") pure $ runExcept do + arr ← readArray log + for arr \el → do + state ← readProp "state" el + method ← readProp "method" el + url ← readProp "url" el + async ← readProp "async" el + password ← unNullOrUndefined <$> readProp "password" el + user ← unNullOrUndefined <$> readProp "user" el pure { state: state , method: method , url: url