webdriver-precore: A typed wrapper for W3C WebDriver protocol. A base for other libraries.

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

This library provides typed definitions for the endpoints of the W3C Webdriver.

It is intended to be used as a base for other libraries that provide a WebDriver client implementation and higher level functions.

A WebDriver client implementation can be built by pattern matching on the W3Spec type returned by the functions in this library, sending the corresponding HTTP requests to a vendor provided WebDriver, then parsing the response using the parser provided as part of the W3Spec type.

See WebDriverPreCore for further details and the project repo for an examples.

If you are looking for a fully implemented client implementation, you should check out an alternative library such as haskell-webdriver.


[Skip to Readme]

Properties

Versions 0.0.0.1
Change log ChangeLog.md
Dependencies aeson (>=1.4 && <2.3), aeson-pretty (>=0.8 && <0.9), base (>=4.16 && <5), bytestring (>=0.10 && <0.12.3), containers (>=0.6 && <0.8), text (>=2.1 && <2.2), vector (>=0.12 && <0.14) [details]
License BSD-3-Clause
Copyright 2025 John Walker, Adrian Glouftsis
Author John Walker, Adrian Glouftsis
Maintainer theghostjw@gmail.com
Category Webb, WebDriver, Testing
Home page https://github.com/pyrethrum/webdriver-precore#readme
Bug tracker https://github.com/pyrethrum/webdriver-precore/issues
Uploaded by JohnWalker at 2025-04-09T08:07:04Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for webdriver-precore-0.0.0.1

[back to package description]

webdriver-precore

What is This Library?

This library provides a minimal abstraction over the WebDriver W3C Protocol endpoints without providing any implementation. It provides a description of the W3C API as a list of functions that return a W3Spec type. The intention is that other libraries will provide the actual implementation.

You can not use this library directly to drive a browser. If you are looking for a fully featured library to drive a browser, you may be interested in an alternative library such as haskell-webdriver, a Selenium 2 client that is actively maintained.

Why This Library?

Several libraries provide WebDriver bindings for Haskell. However, when development on this library began, the existing options were either unmaintained, dependent on Selenium, or tightly coupled with larger, opinionated testing frameworks.

The authors aim to develop a set of low-level libraries to support web UI testing within our standalone test framework, while also making them useful for others. This library is the first in that series.

Core Principles

Library Non-Goals

Acknowledgements

This library would not have been possible without the prior work in:

Haskell (particularly):

Selenium and WebDriver Standards:

The decade+ efforts of the Selenium maintainers, both in forging the way with Selenium and their ongoing work in the development of the W3C standards

Minimal Example

Driving a browser using this library requires the following:

  1. Implement a runner that takes a W3Spec and makes HTTP calls to a running WebDriver
  2. Create an IO API by applying the runner to each of the endpoint functions in this library
  3. Install the desired browser and browser driver
  4. Run the driver
  5. Drive the browser using the IO API

The full source can be found in the example project repo.

1. Implementing a runner

The first step in writing a WebDriver implementation is to choose an HTTP library. In this example, the chosen library is req.

Then to implement a run function requires the following:

  1. Transform a W3Spec to RequestParams compatible with the chosen HTTP library.
  2. Make an HTTP call to WebDriver as per the RequestParams and return a simplified HttpResponse.
  3. Use the parser provided by the W3Spec to transform the HttpResponse to the desired result type and handle any errors.

Main Types (Used in the Runner)

The two most important types in this library are:

W3Spec

The W3Spec returned by each of this library's endpoint functions. This type represents a driver endpoint.

data W3Spec a
  = Get
      { description :: Text,
        path :: UrlPath,
        parser :: HttpResponse -> Result a
      }
  | Post
      { description :: Text,
        path :: UrlPath,
        body :: Value,
        parser :: HttpResponse -> Result a
      }
  | PostEmpty
      { description :: Text,
        path :: UrlPath,
        parser :: HttpResponse -> Result a
      }
  | Delete
      { description :: Text,
        path :: UrlPath,
        parser :: HttpResponse -> Result a
      }
HttpResponse

HttpResponse is consumed by the parser provided by this library and needs to be constructed by the runner

data HttpResponse = MkHttpResponse
  { -- | HTTP status code.
    statusCode :: Int,
    -- | HTTP status message.
    statusMessage :: Text,
    -- | Response body in JSON format.
    body :: Value
  }

The Runner

source

run :: W3Spec a -> IO a
run spec = do
  -- 1. Convert W3Spec to params for req
  let request = mkRequest spec
  -- 2. Call WebDriver server (via req) and return a simplified HttpResponse 
  response <- callReq request
  -- 3. Apply the W3Spec parser to the HttpResponse get result type and handle errors  
  parseResponse spec response  

1.1 Convert W3Spec to params for req

W3Spec -> ReqRequestParams

-- A custom data type specific to req
data ReqRequestParams where
  MkRequestParams ::
    (HttpBodyAllowed (AllowsBody method) (ProvidesBody body), HttpMethod method, HttpBody body) =>
    { url :: Url 'Http,
      method :: method,
      body :: body,
      port :: Int
    } ->
    ReqRequestParams

-- W3Spec -> ReqRequestParams
-- the url and port would not normally be hard coded
mkRequest :: forall a. W3Spec a -> ReqRequestParams
mkRequest spec = case spec of
  Get {} -> MkRequestParams url GET NoReqBody 4444 
  Post {body} -> MkRequestParams url POST (ReqBodyJson body) 4444
  PostEmpty {} -> MkRequestParams url POST (ReqBodyJson $ object []) 4444
  Delete {} -> MkRequestParams url DELETE NoReqBody 4444
  where
    url =  foldl' (/:) (http "127.0.0.1") spec.path.segments

1.2 Call the WebDriver

ReqRequestParams -> HttpResponse

callReq :: ReqRequestParams -> IO HttpResponse
callReq MkRequestParams {url, method, body, port = prt} =
  runReq defaultHttpConfig {httpConfigCheckResponse = \_ _ _ -> Nothing} $ do
    r <- req method url body jsonResponse $ port prt
    pure $
      MkHttpResponse
        { statusCode = responseStatusCode r,
          statusMessage = responseStatusText r,
          body = responseBody r :: Value
        }
  where
    responseStatusText = decodeUtf8Lenient . responseStatusMessage

1.3 Parse HttpResponse Using the Parser Provided in the W3Spec

HttpResponse -> Return Type

-- in this implementation we are just throwing exceptions on failure
parseResponse :: W3Spec a -> HttpResponse -> IO a
parseResponse spec r =
  spec.parser r
    & \case
      Error msg -> fail $ parseWebDriverError r & \case
          e@NotAnError {} -> unpack spec.description <> "\n" <> 
                            "Failed to parse response:\n " <> msg <> "\nin response:" <> show e
          e@UnrecognisedError {} -> "UnrecognisedError:\n " <> "\nin response:" <> show e
          e@WebDriverError {} -> "WebDriver error thrown:\n " <> show e
      Success a -> pure a

2. Applying the Runner to the W3Spec Functions

Create an IO API by applying run to each endpoint definition exposed by this library

The full source for can be found in the example project repo.

module IOAPI where 

import Data.Aeson (Value)
import Data.Text  as T (Text)
import WebDriverPreCore (DriverStatus, ElementId, Selector, SessionId)
import WebDriverPreCore qualified as W
import Prelude hiding (log)
import IOUtils (sleepMs, encodeFileToBase64)
import IORunner (run)

status :: IO DriverStatus
status = run W.status

newSession :: W.FullCapabilities -> IO SessionId
newSession = run . W.newSession

getTimeouts :: SessionId -> IO W.Timeouts
getTimeouts = run . W.getTimeouts

setTimeouts :: SessionId -> W.Timeouts -> IO ()
setTimeouts s = run . W.setTimeouts s

getCurrentUrl :: SessionId -> IO Text
getCurrentUrl = run . W.getCurrentUrl

getTitle :: SessionId -> IO Text
getTitle = run . W.getTitle

maximizeWindow :: SessionId -> IO W.WindowRect
maximizeWindow = run . W.maximizeWindow

-- ... and 50+ more API functions

3. Install a Vendor Provided WebDriver

Once all the required endpoints are implemented you will be able to interact with browsers via WebDriver

Examples:

  1. firefox
  2. chrome
  3. edge
  4. opera
  5. safari

Ensure the corresponding browser is installed on your system

4. Launch WebDriver From the Terminal

e.g. For Firefox and geckodriver on Linux or WSL you could start geckodriver from the terminal as follows:

Note: we are setting the port to 4444, which is the hard coded port in our example.

> pkill -f geckodriver || true  && geckodriver --port=4444 &

or with logging:

> pkill -f geckodriver || true  && geckodriver --log trace --port=4444 &

or similarly for Chrome and chromedriver:

> pkill -f chromedriver || true && chromedriver --port=4444 &

or with logging:

> pkill -f chromedriver || true && chromedriver --log-level=ALL --port=4444 &

5. Drive the Browser Via the IO API

With the driver running you can now run code that interacts with the browser:

Full source file can be found in the example project repo.

demoForwardBackRefresh :: IO ()
demoForwardBackRefresh = do
  ses <- newSession $ minFullCapabilities Firefox
  navigateTo ses "https://the-internet.herokuapp.com/"
  link findElement ses $ CSS "#content ul:nth-child(4) > li:nth-child(6) > a:nth-child(1)"
  elementClick ses link
  back ses
  forward ses
  refresh ses
  deleteSession ses

This is a minimal API. There is plenty of scope to build on this to provide more constrained types, user-friendly functions and capabilites such as retries, and session and driver management.