DEV Community

Deyan Petrov
Deyan Petrov

Posted on • Updated on

BDD-style Testing in F# with Xunit.Gherkin, GherkinProvider and TickSpec

TLDR: Use TickSpec in F# for BDD-style tests, and utilize the classless or module/function-based approach with a Context record type being passed between the individual step functions.

Note: The below requires basic knowledge of Behavior-Driven Development/ Specification By Example / Gherkin.

Over the years BDD has been helping me immensely to document the software systems I build "for free" while writing functional tests for them. Naturally, after moving to F#, one of the first topics for me was what is the most suitable BDD framework for F#?
I had prior experience with SpecFlow in C#, and even though SpecFlow is an amazing tool with excellent IDE integration, sometimes it was getting in my way due to its code-generation approach, and its general "heaviness". So not only did I want to find a BDD framework in F#, but I wished it were a bit more lightweight than SpecFlow.

This blog post contains a short analysis of the following 3 approaches, but starts with a plain-old Xunit just for the sake of basic introduction:

1) Xunit.GherkinQuick
2) GherkinProvider
3) TickSpec

But before we start - what are we testing? I have selected a set of very simple functions based on NCrontab:

module Framework.Crontab

open System
open NCrontab

/// Parses 5 (standard) or 6 (with seconds) component crontab expressions
let parse (crontabExpression:string) : CrontabSchedule =
    let crontabComponentCount = crontabExpression.Split(" ", StringSplitOptions.RemoveEmptyEntries).Length
    CrontabSchedule.Parse (crontabExpression, CrontabSchedule.ParseOptions ( IncludingSeconds = (crontabComponentCount = 6) ))

/// For start and stop crontabs, e.g. start every day in the morning and stop every day in the evening
let isRunning
    startScheduleCrontab
    stopScheduleCrontab
    maxStartedDurationHours
    maxStoppedDurationHours
    (pointInTime:DateTime)
    =
    let startSchedule = parse startScheduleCrontab
    let stopSchedule = parse stopScheduleCrontab

    let lastStart = startSchedule.GetNextOccurrences(pointInTime.AddHours(-1.0 * maxStartedDurationHours), pointInTime) |> Seq.tryLast
    let lastStop = stopSchedule.GetNextOccurrences(pointInTime.AddHours(-1.0 * maxStoppedDurationHours), pointInTime) |> Seq.tryLast
    //let nextStart = startSchedule.GetNextOccurrences(pointInTime, pointInTime.AddHours(maxStoppedDurationHours)) |> Seq.tryHead
    //let nextStop = stopSchedule.GetNextOccurrences(pointInTime, pointInTime.AddHours(maxStartedDurationHours)) |> Seq.tryHead

    match lastStart, lastStop with
    | Some lastStart, Some lastStop ->
        lastStart > lastStop 
    | None, _ ->
        failwithf "LastStart could not be found using startScheduleCrontab %s and maxStartedDurationHours %f" startScheduleCrontab maxStartedDurationHours
    | _, None ->
        failwithf "LastStop could not be found using stopScheduleCrontab %s and maxStoppedDurationHours %f" stopScheduleCrontab maxStoppedDurationHours

/// For single execution crontabs, e.g. once daily
let getLastRunOn
    runScheduleCrontab
    maxRunIntervalHours
    (pointInTime:DateTime)
    : DateTime    
    =
    let runSchedule = parse runScheduleCrontab
    let lastRunOn = runSchedule.GetNextOccurrences(pointInTime.AddHours(-1.0 * maxRunIntervalHours), pointInTime) |> Seq.tryHead
    match lastRunOn with
    | Some lastRunOn ->
        lastRunOn 
    | None ->
        failwithf "LastRun could not be found using runScheduleCrontab %s and maxRunIntervalHours %f" runScheduleCrontab maxRunIntervalHours

Enter fullscreen mode Exit fullscreen mode

In a nutshell, given a crontab expression for a job with start and stop schedules the function isRunning is telling you whether the job is running for a given point in time. The function getLastRun gives you the last time a single execution job has run calculated from a given point in time.

Plain-old Xunit

Below is how this could be implemented without BDD-style feature file with Given/When/Thens, just with code:

module Framework.Crontab.Tests.Xunit

open System
open Xunit
open Framework.SimpleTypes.TypeExtensions

let parseExamples =
    [|
        [| "0 0 2 * *" |]
        [| "0 0 2 * * *"  |]
    |]

[<Theory; MemberData("parseExamples")>]
let ``Crontab Parsing`` (crontabExpression:string) =
    //When crontab expression <CrontabExpression> is parsed
    let crontabSchedule = Framework.Crontab.parse crontabExpression

    //Then the CrontabSchedule has the same string representation
    Assert.True(crontabSchedule.ToString() = crontabExpression, "Parsed crontabSchedule.ToString() not equal to original crontab expression")

let isRunningExamples =
    [|
        [| DateTime.ParseUtcIso("2020-10-21T00:00:00Z") :> obj; false :> obj |]
        [| DateTime.ParseUtcIso("2020-10-21T08:00:00Z"); true |]
    |]

[<Theory; MemberData("isRunningExamples")>]
let ``Running/Not Running Interval is identified successfully`` (pointInTime:DateTime) (isRunningExpected:bool) =
    //When isRunning is called at <PointInTime> with the following parameters
    let isRunningActual = 
        Framework.Crontab.isRunning
            "0 7 * * 1-5"
            "0 16 * * 1-5"
            72.0
            72.0
            pointInTime

    //Then the isRunning result is <Result>
    Assert.Equal(isRunningExpected, isRunningActual)

let getLastRunOnExamples =
    [|
        [| DateTime.ParseUtcIso("2020-10-21T00:00:00Z") :> obj; DateTime.ParseUtcIso("2020-10-20T02:00:00Z") :> obj |]
        [| DateTime.ParseUtcIso("2020-10-21T08:00:00Z"); DateTime.ParseUtcIso("2020-10-21T02:00:00Z") |]
    |]

[<Theory; MemberData("getLastRunOnExamples")>]
let ``Last Run DateTime is retrieved successfully`` (pointInTime:DateTime) (lastRunOnExpected:DateTime) =
    //When getLastRunOn is called at <PointInTime> with the following parameters
    let lastRunOnActual =
        Framework.Crontab.getLastRunOn
            "0 0 2 * * *"
            24.0
            pointInTime

    //Then the getLastRunOn result is <Result>
    Assert.Equal(lastRunOnExpected, lastRunOnActual)

Enter fullscreen mode Exit fullscreen mode

The points of interest here are:

  1. Theory with MemberData is used to feed the test function with multiple inputs and expected outputs
  2. Comments are used to identify the Given/When/Then (or Arrange/Act/Assert) parts of the test, as all of these are bundled together in the same F# function
  3. The xunit test (=function) names cannot generally accommodate Given/When/Then, as then they would become too long ...

Before I start listing the BDD/Gherkin testing options, here is the feature file containing the Gherkin language-based scenarios:

Feature: Crontab Tests

  Scenario Outline: Crontab Parsing
    When crontab expression <CrontabExpression> is parsed
    Then the CrontabSchedule has the same string representation

    Examples:
      | CrontabExpression |
      | 0 0 2 * *         |
      | 0 0 2 * * *       |

  Scenario Outline: Running/Not Running Interval is identified successfully
    When isRunning is called at <PointInTime> with the following parameters
      | Parameter               | Value        |
      | startScheduleCrontab    | 0 7 * * 1-5  |
      | stopScheduleCrontab     | 0 16 * * 1-5 |
      | maxStartedDurationHours | 72           |
      | maxStoppedDurationHours | 72           |
    Then the isRunning result is <Result>

    Examples:
      | PointInTime          | Result |
      | 2020-10-21T00:00:00Z | false  |
      | 2020-10-21T08:00:00Z | true   |

  Scenario Outline: Last Run DateTime is retrieved successfully
    When getLastRunOn is called at <PointInTime> with the following parameters
      | Parameter           | Value       |
      | runScheduleCrontab  | 0 0 2 * * * |
      | maxRunIntervalHours | 24          |
    Then the getLastRunOn result is <Result>

    Examples:
      | PointInTime          | Result               |
      | 2020-10-21T00:00:00Z | 2020-10-20T02:00:00Z |
      | 2020-10-21T08:00:00Z | 2020-10-21T02:00:00Z |    
Enter fullscreen mode Exit fullscreen mode

Xunit.Gherkin.Quick

There is a hidden gem for Xunit called Xunit.Gherkin.Quick which allows you to create standard feature files using the Gherkin language, and automate these with Xunit-based tests.

As usual a nuget package reference is required:

<PackageReference Include="Gherkin.TypeProvider" Version="0.1.10" />
Enter fullscreen mode Exit fullscreen mode

As usual a nuget package reference is required:

<PackageReference Include="Xunit.Gherkin.Quick" Version="4.1.0" />
Enter fullscreen mode Exit fullscreen mode

The feature file must be in some folder (e.g. in the project folder), but it does not need to be added to the fproj file in a special way (Content/EmbeddedResource).

Here is how the code based on Xunit.Gherkin.Quick could look like:

module Framework.Crontab.Tests.XunitGherkinQuick

open System
open Gherkin.Ast
open NCrontab
open Xunit
open Xunit.Gherkin.Quick
open Framework.SimpleTypes.TypeExtensions

module Table =
    let getValueByKey key (dt:DataTable) : string =
        dt.Rows
        |> Seq.find (fun x ->
            let cells = x.Cells |> List.ofSeq
            cells.[0].Value = key)
        |> (fun r -> r.Cells)
        |> Seq.last
        |> (fun c -> c.Value)

[<Xunit.Gherkin.Quick.FeatureFile("./CrontabTests.feature")>]
type CrontabTests() =
    inherit Feature()

    let mutable ctxCrontabExpression = None
    let mutable ctxCrontabSchedule : CrontabSchedule option = None

    let mutable isRunningActual: bool option = None

    let mutable lastRunOnActual: DateTime option = None

    [<When("crontab expression (.+) is parsed")>]
    member this.``When crontab expression <CrontabExpression> is parsed`` (crontabExpression:string) =
        ctxCrontabExpression <- crontabExpression |> Some
        ctxCrontabSchedule <- Framework.Crontab.parse crontabExpression |> Some

    [<Then("the CrontabSchedule has the same string representation")>]
    member this.``Then the CrontabSchedule has the same string representation`` () =
        Assert.True(ctxCrontabSchedule.Value.ToString() = ctxCrontabExpression.Value, "Parsed crontabSchedule.ToString() not equal to original crontab expression")

    [<When("isRunning is called at (.*) with the following parameters")>]
    member this.``When isRunning is called at <PointInTime> with the following parameters`` (pointInTime:string) (datatable:DataTable) =
        isRunningActual <- 
            Framework.Crontab.isRunning
                (Table.getValueByKey "startScheduleCrontab" datatable |> string)
                (Table.getValueByKey "stopScheduleCrontab" datatable |> string)
                (Table.getValueByKey "maxStartedDurationHours" datatable |> Convert.ToDouble)
                (Table.getValueByKey "maxStoppedDurationHours" datatable |> Convert.ToDouble)
                (pointInTime |> DateTime.ParseUtcIso)
            |> Some

    [<Then("the isRunning result is (.*)")>]
    member this.``Then the isRunning result is <Result>`` (isRunningExpected:bool) =
        Assert.Equal(isRunningExpected, isRunningActual.Value)

    [<When("getLastRunOn is called at (.*) with the following parameters")>]
    member this.``When getLastRunOn is called at <PointInTime> with the following parameters`` (pointInTime:string) (datatable:DataTable) =
        lastRunOnActual <-
            Framework.Crontab.getLastRunOn
                (Table.getValueByKey "runScheduleCrontab" datatable |> string)
                (Table.getValueByKey "maxRunIntervalHours" datatable |> Convert.ToDouble)
                (pointInTime |> DateTime.ParseUtcIso)
            |> Some

    [<Then("the getLastRunOn result is (.*)")>]
    member this.``Then the getLastRunOn restheult is <Result>`` (lastRunOnExpected:string) =
        Assert.Equal(lastRunOnExpected |> DateTime.ParseUtcIso, lastRunOnActual.Value)
Enter fullscreen mode Exit fullscreen mode

The points of interest here are:

  1. The feature file is referenced using a class attribute, which automatically means you must have 1 class per feature file (which turns out to be a good thing)
  2. The function names can be anything, here I have just used 1:1 the step text, because the actual mapping between a step (= line in the feature file) and a method in the implementation is done by using method-level attributes. This is a bit of a hassle, because you wonder how to name your methods ...
  3. Mutable variables are used to transfer state from Given->When->Then step functions

GherkinProvider

Gherkin Provider is a F# Type Provider, which means it automatically generates types based on the feature file while you are typing in your IDE - magic! ;) I was (and still am) very excited when I first saw it, as it has the promise to bring the best of 2 worlds:

  1. Scenarios + Examples extracted into a very readable feature file
  2. Code for Given/When/Then residing in the same function!

As usual a nuget package reference is required:

<PackageReference Include="Gherkin.TypeProvider" Version="0.1.10" />
Enter fullscreen mode Exit fullscreen mode

The feature file must be added to the project as Content, e.g.:

<Content Include="CrontabTests.feature" />
Enter fullscreen mode Exit fullscreen mode

Below an implementation with it:

module Framework.Crontab.Tests.GherkinProvider

open System
open Xunit
open FSharp.Data.Gherkin
open GherkinProvider.Validation
open Xunit.Extensions.Ordering
open Framework.SimpleTypes.TypeExtensions

type TestFeature = GherkinProvider<const(__SOURCE_DIRECTORY__ + "/CrontabTests.feature")>
let feature = TestFeature.CreateFeature()

let assertScenarioInSync (scenario:TestFeature.TestFeature_ScenarioBase) =
    Assert.True(scenario.Visited)
    scenario.Steps |> Array.iter (fun x -> Assert.True(x.Visited))

let parseExamples =
    feature.Scenarios.``Crontab Parsing``.Examples
    |> Array.map (fun x -> [|x.CrontabExpression.Value|])

[<Theory; MemberData("parseExamples")>]
let ``Parsing of Crontabs works`` (crontabExpression:string) =
    let scenario = feature.Scenarios.``Crontab Parsing``

    scenario.``0 When crontab expression <CrontabExpression> is parsed`` |> ignore
    let crontabSchedule = Framework.Crontab.parse crontabExpression

    scenario.``1 Then the CrontabSchedule has the same string representation`` |> ignore
    Assert.True(crontabSchedule.ToString() = crontabExpression, "Parsed crontabSchedule.ToString() not equal to original crontab expression")

    assertScenarioInSync scenario

let isRunningExamples =
    feature.Scenarios.``Running_Not Running Interval is identified successfully``.Examples
    |> Array.map (fun x -> [|x.PointInTime.Value; x.Result.Value|])

[<Theory; MemberData("isRunningExamples")>]
let ``Running/Not Running Interval is identified successfully`` (pointInTime:string) (isRunningExpected:string) =
    let scenario = feature.Scenarios.``Running_Not Running Interval is identified successfully``

    scenario.``0 When isRunning is called at <PointInTime> with the following parameters`` |> ignore
    let getValueByKey key =
        scenario.``0 When isRunning is called at <PointInTime> with the following parameters``.Argument
        |> Array.filter (fun i -> i.Parameter.Value = key)
        |> Array.head
        |> (fun x -> x.Value.Value)

    let isRunningActual = 
        Framework.Crontab.isRunning
            (getValueByKey "startScheduleCrontab" |> string)
            (getValueByKey "stopScheduleCrontab" |> string)
            (getValueByKey "maxStartedDurationHours" |> Convert.ToDouble)
            (getValueByKey "maxStoppedDurationHours" |> Convert.ToDouble)
            (pointInTime |> DateTime.ParseUtcIso)

    scenario.``1 Then the isRunning result is <Result>`` |> ignore
    Assert.Equal(isRunningExpected |> bool.Parse, isRunningActual)

    assertScenarioInSync scenario

let getLastRunOnExamples =
    feature.Scenarios.``Last Run DateTime is retrieved successfully``.Examples
    |> Array.map (fun x -> [|x.PointInTime.Value; x.Result.Value|])

[<Theory; MemberData("getLastRunOnExamples")>]
let ``Last Run DateTime is retrieved successfully`` (pointInTime:string) (lastRunOnExpected:string) =
    let scenario = feature.Scenarios.``Last Run DateTime is retrieved successfully``

    scenario.``0 When getLastRunOn is called at <PointInTime> with the following parameters`` |> ignore
    let getValueByKey key =
        scenario.``0 When getLastRunOn is called at <PointInTime> with the following parameters``.Argument
        |> Array.filter (fun i -> i.Parameter.Value = key)
        |> Array.head
        |> (fun x -> x.Value.Value)    

    let lastRunOnActual =
        Framework.Crontab.getLastRunOn
            (getValueByKey "runScheduleCrontab" |> string)
            (getValueByKey "maxRunIntervalHours" |> Convert.ToDouble)
            (pointInTime |> DateTime.ParseUtcIso)
        |> DateTime.ToStringIso

    scenario.``1 Then the getLastRunOn result is <Result>`` |> ignore
    Assert.Equal(lastRunOnExpected |> DateTime.ParseUtcIso, lastRunOnActual |> DateTime.ParseUtcIso)

    assertScenarioInSync scenario

[<Fact; Order(Int32.MaxValue)>]
let validateFeatureVisited () =
    let validator = FeatureValidator()
    match validator.Validate feature with
    | None -> ()
    | Some report -> failwith(report.Summary)

Enter fullscreen mode Exit fullscreen mode

Points of interest:

  1. When you load the feature file it autogenerates a type with a number of neested types (line 10)
  2. The examples are passed to the functions by using standard Xunit Theory + Member Data, very low-level, no magic
  3. Because the sub-types are autogenerated, you cannot easily create functions operating on different subtypes
  4. There are strange statements inside the test functions like scenario. \1 Then the getLastRunOn result is <Result>\|> ignore and there is the validateFeatureVisited invoked at the end (that's why Order(Int32.MaxValue) attribute[^1]) to make sure that all features are visited. I have nothing against the former, as they serve as strongly-typed comments (compare with plain-old Xunit sample at the beginning), but validateFeatureVisited is a bit too much for me ...

TickSpec

TickSpec is the dinasour in the room (dating back to 2010!!) but remarkably straightforward (compared to SpecFlow). It does not use code-generation magic, but it has a little magic related to how steps (in feature files) are mapped to functions and how step parameters (e.g. tables) are mapped to function parameters, and how parameters are passed between Given/When/Then functions.

As usual a nuget package reference is required:

<PackageReference Include="TickSpec" Version="2.0.0"/>
Enter fullscreen mode Exit fullscreen mode

The feature file must be added to the project as Content, e.g.:

<EmbeddedResource Include="CrontabTests.feature" />
Enter fullscreen mode Exit fullscreen mode

An implementation of automated tests for the Crontab functions looks like this:

Features.fs

namespace Framework.Crontab.Tests.TickSpec

open System.Diagnostics
open Framework.Crontab.Tests.TickSpec
open Xunit
open Framework.Testing.TickSpecXunitWiring.Version2

type Features() =
    static let source = AssemblyStepDefinitionsSource(System.Reflection.Assembly.GetExecutingAssembly())
    static let scenarios resourceName = source.ScenariosFromEmbeddedResource resourceName |> MemberData.ofScenarios

    [<Theory; MemberData("scenarios", "Framework.Crontab.Tests.CrontabTests.feature")>]
    member this.CrontabTests (scenario : XunitSerializableScenario) = 
        source.ScenarioAction(scenario).Invoke()

Enter fullscreen mode Exit fullscreen mode

CrontabTests.TickSpec.fs

module Framework.Crontab.Tests.CrontabTests.TickSpec

open System
open NCrontab
open Xunit
open TickSpec
open Framework.Testing.Table
open Framework.SimpleTypes.TypeExtensions

type ParseContext = {
    CrontabExpression : string
    ParsedCrontabSchedule : CrontabSchedule
} 

let [<When>] ``crontab expression (.*) is parsed`` (crontabExpression:string) =
    let crontabSchedule = Framework.Crontab.parse crontabExpression

    {
        CrontabExpression = crontabExpression
        ParsedCrontabSchedule = crontabSchedule
    }

let [<Then>] ``the CrontabSchedule has the same string representation`` (ctx:ParseContext) =
    Assert.True(ctx.ParsedCrontabSchedule.ToString() = ctx.CrontabExpression, "Parsed crontabSchedule.ToString() not equal to original crontab expression")

let [<When>] ``isRunning is called at (.*) with the following parameters`` pointInTime (parameters:Table) =
    Framework.Crontab.isRunning
        (VTable.getValueByKey "startScheduleCrontab" parameters.Rows)
        (VTable.getValueByKey "stopScheduleCrontab" parameters.Rows)
        (VTable.getValueByKey "maxStartedDurationHours" parameters.Rows |> float)
        (VTable.getValueByKey "maxStoppedDurationHours" parameters.Rows |> float)
        (pointInTime |> DateTime.ParseUtcIso)

let [<Then>] ``the isRunning result is (.*)`` (isRunningExpected:string) (isRunningActual:bool) =
    Assert.Equal(isRunningExpected |> bool.Parse, isRunningActual)

let [<When>] ``getLastRunOn is called at (.*) with the following parameters`` pointInTime (parameters:Table) =
    Framework.Crontab.getLastRunOn
        (VTable.getValueByKey "runScheduleCrontab" parameters.Rows)
        (VTable.getValueByKey "maxRunIntervalHours" parameters.Rows |> float)
        (pointInTime |> DateTime.ParseUtcIso)

let [<Then>] ``the getLastRunOn result is (.*)`` (lastRunOnExpected:string) (lastRunOnActual:DateTime) =
    Assert.Equal(lastRunOnExpected |> DateTime.ParseUtcIso, lastRunOnActual)

Enter fullscreen mode Exit fullscreen mode

Points of interest:

  1. There is no need for a class + member methods, just a plain module with functions can be used!
  2. Functions are mapped to steps by name - no need for attributes!
  3. Function arguments are automatically captured by TickSpec based on simple regular expressions
  4. Examples are handled by TickSpec after doing some Xunit wiring involving the usual suspects - Theory and MemberData, however the code is minimal and TickSpec does some function argument magic again

Note the following potential pitfalls related to TickSpec function/argument mapping magic:

  • Initially we did experience some strange error messages related to arguments not mapped correctly, but as soon as we started using a Context record type per feature all these were gone. That one could look like this:
type Context = {
    Value1: int option
    Value2: string option
}

let [<Given>] ``some given step`` () =
    { 
      Value1 = Some 1
      Value2 = None
    }

let [<When>] ``some when step`` () =
    let result = //...
    { ctx with Value2 = Some result }

let [<Then>] ``some then step (.*)`` (someArgOfThisStep: string) (ctx:Context) =
    Assert.Equal(someArgOfThisStep, ctx.Value2.Value)
Enter fullscreen mode Exit fullscreen mode
  • Additionally, quite a few times TickSpec was reporting missing step implementation error, and it turned out we have forgotten the () of a function which has no arguments ;)

In the end we decided to focus on using TickSpec for all our automated tests (yes, including unit tests ... [^2]) due to its elegant approach of mapping steps/examples with functions and their arguments.

P.S. Project can be found at: https://github.com/deyanp/FSharpBDDComparison

[^1] Which requires [<assembly: Xunit.TestCaseOrderer("Xunit.Extensions.Ordering.TestCaseOrderer", "Xunit.Extensions.Ordering")>] in AssemblyInfo.fs or similar
[^2] I/we do not care too much about the question if BDD-style test automation should or should not be used for unit tests. See Behavior Driven Development vs Unit Testing
for a discussion I am not sure I agree 100% with ..

Top comments (0)