Skip to content

Commit

Permalink
Merge pull request #89 from quickstrom/non-empty-actions-dsl
Browse files Browse the repository at this point in the history
New API for actions in DSL
  • Loading branch information
owickstrom committed Mar 11, 2021
2 parents 0b35b73 + fb2de4d commit f11f92a
Show file tree
Hide file tree
Showing 29 changed files with 299 additions and 195 deletions.
2 changes: 1 addition & 1 deletion cli/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ import Data.Text.Prettyprint.Doc.Symbols.Unicode (bullet)
import Options.Applicative
import qualified Pipes as Pipes
import qualified Quickstrom.Browser as Quickstrom
import qualified Quickstrom.Timeout as Quickstrom
import qualified Quickstrom.CLI.Logging as Quickstrom
import Quickstrom.CLI.Reporter (Reporter)
import qualified Quickstrom.CLI.Reporter as Reporter
Expand All @@ -37,6 +36,7 @@ import qualified Quickstrom.LogLevel as Quickstrom
import Quickstrom.Prelude hiding (option, try)
import qualified Quickstrom.PureScript.Program as Quickstrom
import qualified Quickstrom.Run as Quickstrom
import qualified Quickstrom.Timeout as Quickstrom
import qualified Quickstrom.Trace as Quickstrom
import qualified Quickstrom.WebDriver.Class as Quickstrom
import qualified Quickstrom.WebDriver.WebDriverW3C as WebDriver
Expand Down
80 changes: 48 additions & 32 deletions docs/source/topics/specification-language.rst
Original file line number Diff line number Diff line change
Expand Up @@ -191,40 +191,47 @@ Actions
-------

We must instruct Quickstrom what actions it should try. The ``actions``
definition in a specification module has the following type:
definition in a specification module is where you list possible actions.

.. code-block:: haskell
Array (Tuple Int ActionSequence)
actions :: Actions
actions = [ action1, action2, ... ]
It's an array of pairs, or tuples, where each pair holds a weight and a
sequence of actions. The weight specifies the intended probability
of the sequence being picked, relative to the other sequences.
It's an array of values, where each value describes an action or a fixed
sequence of actions. Each action also carries a weight, which specifies the
intended probability of the action being picked, relative to the other
actions.

To illustrate, in the following array of action sequences, the probability of
``a1`` being picked is 40%, while the others are at 20% each. This is assuming
the first action in each sequence is *possible* at each point a sequence is being
picked.
The default weight is ``1``. To override it, use the ``weighted`` function:

.. code-block::
.. code-block:: haskell
click "#important-action" `weighted` 10
To illustrate, in the following array of actions, the probability of ``a1``
being picked is 40%, while the others are at 20% each. This is assuming the
action (or the first action in each sequence) is *possible* at each point a
sequence is being picked.

.. code-block:: haskell
actions = [
Tuple 2 a1,
Tuple 1 a2,
Tuple 1 a3,
Tuple 1 a4
a1 `weighted` 2,
a2,
a3,
a4
]
Action Sequences
~~~~~~~~~~~~~~~~

An action sequence is either a single action or a fixed sequence of actions:
An action sequence is either a single action or a fixed sequence of actions.
Here's a simple sequence:

.. code-block:: haskell
data ActionSequence
= Single Action
| Sequence (Array Action)
backAndForth = click "#back" `followedBy` click "#forward"
A sequence of actions is always performed in its entirety when picked, as
long as the first action in the sequence is considered possible by the test
Expand All @@ -233,36 +240,45 @@ runner.
Actions
~~~~~~~

The ``Action`` data type is defined in the Quickstrom library, along with
some aliases for common actions. For instance, here's the definition of
``foci``:
The available actions are provided in the Quickstrom library:

* ``focus``
* ``keyPress``
* ``enterText``
* ``click``
* ``clear``
* ``await``
* ``awaitWithTimeoutSecs``
* ``navigate``
* ``refresh``

Along with those functions, there are some aliases for common actions. For
instance, here's the definition of ``foci``:

.. code-block:: haskell
-- | Generate focus actions on common focusable elements.
foci :: Actions
foci =
[ Tuple 1 (Single (Focus "input"))
, Tuple 1 (Single (Focus "textarea"))
[ focus "input"
, focus "textarea"
]
More action constructors and aliases should be introduced as Quickstrom
evolves.
More actions and aliases should be introduced as Quickstrom evolves.

Example
~~~~~~~

As an example of composing actions and sequences of actions, here's a
collection of actions that try to log in and to click a buy button:
collection of actions that try to log in or to click a buy button:

.. code-block:: haskell
foci =
[ Tuple 1 (Sequence [ Focus "input[type=password]"
, EnterText "$ecr3tz"
, Click "input[type=submit][name=log-in]"
])
, Tuple 1 (Single (Click "input[type=submit][name=buy]"))
actions =
[ focus "input[type=password]"
`followedBy` enterText "$ecr3tz"
`followedBy` click "input[type=submit][name=log-in]"
, click "input[type=submit][name=buy]"
]
.. note::
Expand Down
1 change: 0 additions & 1 deletion dsl/src/Quickstrom.js
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
exports._next = null;
exports._always = null;
exports._until = null;
exports._log = null;
exports._queryAll = null;
exports._property = null;
exports._attribute = null;
Expand Down
4 changes: 3 additions & 1 deletion dsl/src/Quickstrom.purs
Original file line number Diff line number Diff line change
Expand Up @@ -20,18 +20,20 @@ module Quickstrom
, unchanged
, module Quickstrom.Selector
, module Spec
, module NonEmpty
, module Data.HeytingAlgebra
, module Prelude
) where

import Prelude
import Data.Array (head)
import Data.Maybe (Maybe)
import Data.NonEmpty (NonEmpty(..), (:|)) as NonEmpty
import Data.HeytingAlgebra (implies)
import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)
import Prim.RowList (class RowToList, Cons, Nil, kind RowList)
import Quickstrom.Selector (Selector)
import Quickstrom.Spec (Actions, ProbabilisticAction, Action(..), ActionSequence(..), Path, SpecialKey(..), asciiKeyPresses, clicks, foci, focus, keyPress, specialKeyPress) as Spec
import Quickstrom.Spec (class ToAction, Actions, Path, ProbabilisticAction, SpecialKey(..), asciiKeyPresses, await, awaitWithTimeoutSecs, clear, click, clicks, enterText, foci, focus, keyPress, navigate, refresh, specialKeyPress, toAction, followedBy, weighted) as Spec
import Type.Prelude (class ListToRow, class TypeEquals)

-- ## Temporal operators
Expand Down
108 changes: 80 additions & 28 deletions dsl/src/Quickstrom/Spec.purs
Original file line number Diff line number Diff line change
@@ -1,21 +1,32 @@
module Quickstrom.Spec
( Path
, Action(..)
, ActionSequence(..)
, Action
, Actions
, ProbabilisticAction
, clicks
, class ToAction
, toAction
, followedBy
, weighted
-- Actions
, focus
, foci
, keyPress
, enterText
, click
, clear
, await
, awaitWithTimeoutSecs
, navigate
, refresh
-- Predefined
, clicks
, foci
, asciiKeyPresses
, SpecialKey(..)
, specialKeyPress
) where

import Prelude
import Quickstrom.Selector (Selector)
import Data.Tuple (Tuple(..))

import Data.Array (range)
import Data.Char (fromCharCode)
import Data.Enum (class Enum)
Expand All @@ -25,6 +36,7 @@ import Data.Generic.Rep.Ord (genericCompare)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (fromJust)
import Partial.Unsafe (unsafePartial)
import Quickstrom.Selector (Selector)

-- | URL to a web page, or a relative path within a web site.
type Path
Expand All @@ -43,46 +55,86 @@ data Action
| Navigate Path
| Refresh

-- | Either a single action or a fixed sequence of actions.
data ActionSequence
= Single Action
| Sequence (Array Action)
type Weighted a = {weight :: Int, weighted :: a}

type ProbabilisticAction
= Tuple Int ActionSequence
-- | An action (or fixed sequence of actions) carrying a
-- | weight, representing its relative probability of being chosen.
newtype ProbabilisticAction = ProbabilisticAction (Weighted (Array Action))

-- | An array of tuples, containing probabilistic weights and
-- | action sequences.
type Actions
= Array ProbabilisticAction

-- | Internal class for return type polymorphism in action functions.
class ToAction a where
toAction :: Action -> a

instance toActionAction :: ToAction Action where
toAction = identity

instance toActionProbabilisticAction :: ToAction ProbabilisticAction where
toAction a = ProbabilisticAction { weighted: pure a, weight: 1 }

followedBy :: ProbabilisticAction -> Action -> ProbabilisticAction
followedBy (ProbabilisticAction p) a = ProbabilisticAction (p { weighted = p.weighted <> pure a })

weighted :: ProbabilisticAction -> Int -> ProbabilisticAction
weighted (ProbabilisticAction a) w = ProbabilisticAction a { weight = w }

-- * Actions

focus :: forall a. ToAction a => Selector -> a
focus = toAction <<< Focus

keyPress :: forall a. ToAction a => Char -> a
keyPress = toAction <<< KeyPress

enterText :: forall a. ToAction a => String -> a
enterText = toAction <<< EnterText

click :: forall a. ToAction a => Selector -> a
click = toAction <<< Click

clear :: forall a. ToAction a => Selector -> a
clear = toAction <<< Clear

await :: forall a. ToAction a => Selector -> a
await = toAction <<< Await

awaitWithTimeoutSecs :: forall a. ToAction a => Int -> Selector -> a
awaitWithTimeoutSecs s = toAction <<< AwaitWithTimeoutSecs s

navigate :: forall a. ToAction a => Path -> a
navigate = toAction <<< Navigate

refresh :: forall a. ToAction a => a
refresh = toAction Refresh

-- * Predefined actions

-- | Generate click actions on common clickable elements.
clicks :: Actions
clicks =
[ Tuple 1 (Single $ Click "button")
, Tuple 1 (Single $ Click "input[type=submit]")
, Tuple 1 (Single $ Click "a")
[ click "button" `weighted` 1
, click "input[type=submit]" `weighted` 1
, click "a" `weighted` 1
]

-- | Generate focus actions on elements matching the given selector.
focus :: Selector -> Action
focus = Focus

-- | Generate focus actions on common focusable elements.
foci :: Actions
foci = [ Tuple 1 (Single $ Focus "input"), Tuple 1 (Single $ Focus "textarea") ]

-- | Generate a key press action with the given character.
keyPress :: Char -> Action
keyPress = KeyPress
foci =
[ focus "input" `weighted` 1
, focus "textarea" `weighted` 1
]

-- | Generate key press actions with printable ASCII characters.
asciiKeyPresses :: Array Action
asciiKeyPresses = KeyPress <<< unsafePartial fromJust <<< fromCharCode <$> range 32 126
asciiKeyPresses :: forall a. ToAction a => Array a
asciiKeyPresses = toAction <<< KeyPress <<< unsafePartial fromJust <<< fromCharCode <$> range 32 126

-- | Generate a key press action with the given special key.
specialKeyPress :: SpecialKey -> Action
specialKeyPress specialKey = KeyPress (specialKeyToChar specialKey)
specialKeyPress :: forall a. ToAction a => SpecialKey -> a
specialKeyPress specialKey = toAction (KeyPress (specialKeyToChar specialKey))

data SpecialKey
= KeyAdd
Expand Down
36 changes: 11 additions & 25 deletions html-report/src/App.tsx
Original file line number Diff line number Diff line change
Expand Up @@ -97,9 +97,9 @@ type Action =
| { tag: "Click", contents: [string, number] }
| { tag: "Navigate", contents: string };

type ActionSequence =
{ tag: "Single", contents: Action }
| { tag: "Sequence", contents: Action[] };
type NonEmptyArray<T> = [T, ...T[]];

type ActionSequence = NonEmptyArray<Action>;

type TestViewerState = {
test: Test,
Expand Down Expand Up @@ -352,28 +352,14 @@ const ActionSequence: FunctionComponent<{ actionSequence?: ActionSequence }> = (
}

if (actionSequence) {
switch (actionSequence.tag) {
case "Single":
return (
<div class="action-sequence">
<div class="action-sequence-inner">
<div class="label">Action</div>
{renderDetails(actionSequence.contents)}
</div>
</div>

);
case "Sequence":
return (
<div class="action-sequence">
<div class="action-sequence-inner">
<div class="label">Action Sequence</div>
{actionSequence.contents.map(renderDetails)}
</div>
</div>

);
}
return (
<div class="action-sequence">
<div class="action-sequence-inner">
<div class="label">Action Sequence</div>
{actionSequence.map(renderDetails)}
</div>
</div>
);
} {
return null;
}
Expand Down
8 changes: 4 additions & 4 deletions integration-tests/failing/CommentForm.spec.purs
Original file line number Diff line number Diff line change
Expand Up @@ -11,14 +11,14 @@ readyWhen = "form"

actions :: Actions
actions =
[ Tuple 3 (Single $ Focus "input[type=text]:nth-child(1)")
[ focus "input[type=text]:nth-child(1)" `weighted` 3
-- This spec is flaky. It only finds the bug on some runs, so the following action
-- is commented out to increase chances of a failed example:
--
-- , Tuple 1 (Single $ Focus "input[type=text]:nth-child(2)")
, Tuple 5 (Single $ Click "input[type=submit]")
, Tuple 5 (Single $ KeyPress ' ')
, Tuple 5 (Single $ KeyPress 'a')
, click "input[type=submit]" `weighted` 5
, keyPress ' ' `weighted` 5
, keyPress 'a' `weighted` 5
]

proposition :: Boolean
Expand Down

0 comments on commit f11f92a

Please sign in to comment.