Tuesday, October 20, 2009

Stack Overflow in F# Sequences

Not so long ago, I ran into a curious problem while writing some F# sequence code.

Let's consider a simple function that takes a list and produces a sequence of the reversed list.

let rec reverse l =
  seq { match l with
         |h::t -> yield!  reverse t
                  yield h
         |[] -> yield! Seq.empty
      }
Now let's try to count the number of elements of a very large sequence.
let ls = Seq.to_list (seq {for i in 1..10000000 -> i})

Seq.fold (fun acc _ -> acc+1) 1 (reverse ls)
And here, what happen? We get a stack overflow. Maybe the beginning of an explanation lies in the definition of reverse.

Looking at it, we can see that the recursive call

 yield!  reverse t
appears before yielding the current head of the list. So we have a recursive call that is not in tail position.

That explains the stack overflow.

A solution is to use continuation passing style to move the recursive call to a tail position.

let reverse l =
  let k0 () = Seq.empty
  let rec proc l kc =
     seq { match l with
             |h::t -> let kc' () = seq { yield h
                                         yield! kc()
                                       }
                      yield!  (proc t kc')
             |[] -> yield! kc ()
         }
  proc l k0
Now it works!

Saturday, May 16, 2009

Implementing Equals in C#

In this post I present a way that, in my opinion, correctly implements equality between objects. Or at least, correctly implements equality with respect to some specific objectives. Indeed, there are many ways to write Equals(). But, each way targets some specific goals and I do not believe that there is only one way to do it.

To start with, let's state what the objectives are in this case:

  • Equality for immutable value objects.
  • Two objects are equals iff they are of exactly the same class, independently of the type of the variable that holds them.
  • Support inheritance and reuse comparison logic from base classes.
  • Support the == operator.
  • Reduce the programmer's workload as much as possible.
The code is below:

using System;
using System.Collections.Generic;
using System.Linq;
using System.Text;

namespace Equal
{
    public class Util
    {
        // Returns true if a and b are both non null and are of exactly the same class
        public static bool AreSameClass(Object a, Object b)
        {
            return a != null && b != null && a.GetType().Equals(b.GetType());
        }
    }

    public class A
    {
        private int a;

        public A(int a)
        {
            this.a = a;
        }

        public override int GetHashCode()
        {
            return a;
        }

        public override bool Equals(object o)
        {
            return Util.AreSameClass(this, o) && this.EqualMembers((A)o);
        }

        protected bool EqualMembers(A o)
        {
            return a == o.a;
        }

        public static bool operator ==(A a, A b)
        {
            return object.Equals(a, b); // handle cases where a or b is null.
        }

        public static bool operator !=(A a, A b)
        {
            return !(a == b);
        }
    }

    public class B : A
    {
        public int b;

        public B(int a, int b)
            : base(a)
        {
            this.b = b;
        }

        public override int GetHashCode()
        {
            return base.GetHashCode() + b;
        }

        public override bool Equals(object o)
        {
            return Util.AreSameClass(this, o) && this.EqualMembers((B)o);

        }

        protected bool EqualMembers(B o)
        {
            return base.Equals(o) && b == o.b;
        }
    }
}
The Util class is a helper class that helps find whether two objects are of the same class. If at least one is null then the objects are considered not being of the same class. As we will see later, the handling of null objects is done elsewhere. Then comes the base class A. This class follows the good practices in term of implementation of GetHashCode().

In addition:

  • The class A overrides A.Equals(object o). It first tests whether this and the object to be compared to are of the same class, using for that the above mentionned Util class. If both objects are of the same class, it then calls the protected, non virtual A.EqualMembers(A o) method to compare two by two the member variables of the class A.
  • As said before, the class A implements A.EqualMembers(A o) . This function compares two objects of type A with respect to their member variables. For this, it does it in the most appropriate way. That is, by invoking Equals(), the == operator or object.ReferenceEquals() if necessary. A.EqualMembers(A o) is not meant to be redefined by subclasses. If that should happen, the subclass should simply calls base.EqualMembers(A o).
  • Class A also implements the dual operators == and != operators. The == operator calls objects.Equals(), making sure that nulls are handled properly.
The implementation of equals for subclass B is not more complex:

  • Class B implements GetHashCode() which calls base.GetHashCode().
  • Class B implements B.equals(object o) the same way as class A.
  • Class B implements EqualMembers(B o). This method first calls base.EqualMembers(o) in order to compare the member variables defined by class A and then compares the member variables defined by class B.
  • Class B does not need to implements the == operator anymore.
One can ask why we have defined the non virtual methods EqualMember(). Usually, the role of comparing objects in a type safe way is given to IEquatable.Equals(T o). The answer is simple, in that case, two objects of the same type (B) which are different but whose common parts (A) are the same would be equal if the equality is tested from within a method of class B. In other words, the equality would return different results depending on the caller's context.

This is shown in the code below:


using System;
using System.Collections.Generic;
using System.Linq;
using System.Text;

namespace Equal
{
public class Util
{
  // Returns true if a and b are both non null and are of exactly the same class
  public static bool AreSameClass(Object a, Object b)
  {
      return a != null && b != null && a.GetType().Equals(b.GetType());
  }
}

public class A
{
  private int a;

  public A(int a)
  {
      this.a = a;
  }

  public override int GetHashCode()
  {
      return a;
  }

  public override bool Equals(object o)
  {
      return Util.AreSameClass(this, o) && this.Equals((A)o);
  }

  protected bool Equals(A o)
  {
      return a == o.a;
  }

  public static bool operator ==(A a, A b)
  {
      return object.Equals(a, b); // handle cases where a or b is null.
  }

  public static bool operator !=(A a, A b)
  {
      return !(a == b);
  }
}

public class B : A
{
  public int b;

  public B(int a, int b)
      : base(a)
  {
      this.b = b;
  }

  public override int GetHashCode()
  {
      return base.GetHashCode() + b;
  }

  public override bool Equals(object o)
  {
      return Util.AreSameClass(this, o) && this.Equals((B)o);

  }

  protected bool Equals(B o)
  {
      return base.Equals(o) && b == o.b;
  }

  static public void test()
  {
      B b1 = new B(1, 2);
      B b2 = new B (1,3);

      // casts
      A a2 = b2;

      // returns true althought b1 and b2 are different
      bool r = b1.Equals(a2);
 }
}
}

To finish, here is a set of test cases:

using System;
using System.Collections.Generic;
using System.Linq;
using System.Text;

namespace Equal
{
class Program
{
 static void Main(string[] args)
 {
     B b1 = new B(1, 2);
     B b2 = new B(1, 3);
     B b3 = new B(1, 2);

     // casts
     A a1 = b1;
     A a2 = b2;
     A a3 = b3;

     object o1 = b1;
     object o2 = b2;
     object o3 = b3;

     bool r = true;

     r &= b1.Equals(b1);
     r &= b1.Equals(a1);
     r &= b1.Equals(o1);

     r &= a1.Equals(b1);
     r &= a1.Equals(a1);
     r &= a1.Equals(o1);

     r &= o1.Equals(b1);
     r &= o1.Equals(a1);
     r &= o1.Equals(o1);

     r &= b1 == b1;
     r &= b1 == a1;
     r &= (b1 == o1);  // reference equality

     r &= a1 == b1;
     r &= a1 == a1;
     r &= (a1 == o1);  // reference equality

     r &= (o1 == b1);  // reference equality
     r &= (o1 == a1);  // reference equality
     r &= (o1 == o1);  // reference equality


     r &= !(b1.Equals(b2));
     r &= !(b1.Equals(a2));
     r &= !(b1.Equals(o2));

     r &= !(a1.Equals(b2));
     r &= !(a1.Equals(a2));
     r &= !(a1.Equals(o2));

     r &= !(o1.Equals(b2));
     r &= !(o1.Equals(a2));
     r &= !(o1.Equals(o2));

     r &= !(b1 == b2);
     r &= !(b1 == a2);
     r &= !(b1 == o2);  // reference equality

     r &= !(a1 == b2);
     r &= !(a1 == a2);
     r &= !(a1 == o2);  // reference equality

     r &= !(o1 == b2);  // reference equality
     r &= !(o1 == a2);  // reference equality
     r &= !(o1 == o2);  // reference equality


     r &= b1.Equals(b3);
     r &= b1.Equals(a3);
     r &= b1.Equals(o3);

     r &= a1.Equals(b3);
     r &= a1.Equals(a3);
     r &= a1.Equals(o3);

     r &= o1.Equals(b3);
     r &= o1.Equals(a3);
     r &= o1.Equals(o3);

     r &= b1 == b3;
     r &= b1 == a3;
     r &= !(b1 == o3);  // reference equality

     r &= a1 == b3;
     r &= a1 == a3;
     r &= !(a1 == o3);  // reference equality

     r &= !(o1 == b3);  // reference equality
     r &= !(o1 == a3);  // reference equality
     r &= !(o1 == o3);  // reference equality 
 }
}
}

Sunday, April 26, 2009

Applicative functors: mapping a function to more than 3 lists

Hello

Here is a short post that illustrates the power of higher level functions.

Everybody knows the List.map function that applies an arbitrary function to a list, producing a new list.

#light

List.map (fun x -> 2*x) [1;2]
List.map takes a function of one argument but there also exist List.map2 and List.map3 that take, respectively, a function of 2 and 3 arguments.
List.map2(fun x y -> x+y) [1;2] [1;2]

List.map3 (fun x y z -> x+y+z) [1;2] [1;2] [1;2]
But how do we do if we need a function List.map4 or List.map5 ? The straightforward solution is to explicitly write these functions.

I will show that List.map3, List.map4 or even List.map45 are not needed and with the help of a little operator, we can get the same functionality by simple composition.

First, let's try to evaluate the expression:

List.map (fun x y -> x+y) [1;2]
We get the signature:
val it : (int -> int) list
A list of functions. Clearly, if we combined this list with a list of int (i.e. [3;4]) , making sure that each function is applied to its corresponding integer, we could obtain the same result as the expression:
List.map2 (fun x y -> x+y)  [1;2]  [3;4]
That is precisely what the operator <$> below does:
let (<$>) fctList list = List.map2 (fun fct elem -> fct elem) fctList list
Using both List.map and <$>, we can implement any mapping we want. I.e.
let r = List.map (fun x y z -> x+y+z) [1;2] <$> [1;2] <$> [1;2]
is equivalent to
List.map3 (fun x y z -> x+y+z) [1;2] [1;2] [1;2]
We can also, if we want, explicitly define the equivalent of List.map4
let map4 f l1 l2 l3 l4 = List.map f l1 <$> l2 <$> l3 <$> l4
This technique works also for other types than list. It works with sequence, array... In short it works with any type supporting a map like function.

In the litterature (and more specifically in Haskell) all the types that support a mapping function form the class of Functors.

The types that support both a mapping function and the operator <> belong to the class of gt; belong to the class of Applicative Functors.

Functional Reactive Programming in F# (4)

In this post, I will introduce events in FRP.

Remember, a FRP is used to model systems that have an evolution with respect to continuous time. However the way such a system computes its output(s) may be modified at discrete moments in time. To take a simple example, suppose we want to simulate a ball moving in one direction along a horizontal axis at constant speed. Suppose also that wa have an input device with two controls, the first control sets the velocity of the ball and the second is a button that, when pressed, changes the direction of the ball. Moreover, the ball is only allowed to move between 2 vertical walls. Each time the ball hits one of these walls, its velocity changes direction. This system behaves continuously until one of the three following events occur:

  • The user changes speed.
  • The user presses the velocity direction button.
  • The ball hits a wall.
The first two events are what I called external events. External events are generated from outside of the system. They do not depend on a particular state of the system. They can occur at any moment in time. The third event is not generated by an external source but occurs when the state of the system (here, the ball's position) satisfies some condidtions. I call such events internal events.

The goal of this post is to discuss such internal events.

Some let's start with our Behavior type and its run function.

#light


type Time = float

type 'a Beh  = Beh of (Time -> ('a * 'a Beh))

let rec run (Beh bf) l =
   match l with
   |[] -> []
   |h::t -> let (r, nb) = bf h
            r::(run nb t)
I will not propose to implement the above case with the ball and the walls since this is still a bit too complex for the moment and would hide some important concepts. That is why I prefer an simpler example of a colored Behavior that is white at the beginning of its life and becomes black after some time (namely 10 units of time - i.e seconds). As usual, let's start the "hard way" by manually coding all the logic. Helpful combinators will be derived from this first coding.
type Color = White|Black

// a constant Behavior that is always Black
let rec blackB = Beh (fun t -> (Black, blackB))

let rec colorB =
   let bf t =  if (t<10.0)
               then (White, colorB)
               else let rec blackB = Beh (fun t -> (Black, blackB))
                    (Black, blackB)
   Beh bf

Looking at colorB, it is easy to see that it stays the same, it is always White. When the time reaches 10 seconds, colorB transforms itself into blackB.
let s = Seq.to_list (seq { for x in 1 .. 15 -> (float) x})

let r = run colorB s
As always, the name of the game is to find abstractions (that is, combinators) to help us writing such event handling logic.

The next step is to move the event detection outside of the Behavior function. This is done by defining a cond function that returns None if time is less than 10 seconds and Some blackB when time is higher than or equal to 10 seconds.

The cond function acts as a sort of event generator for colorB.

Now, the Behavior function (bf) invoques cond and tests whether it returns None of Some newBehavior. If cond returns None, then the colorB Behaviors stays the same else colorB becomes the new Behavior returns by cond (newBehavior). We can ask ourselves what we have gained here. The main advantage is that the logic of producing the event is now separated from the handling of the event.

Moreover the handling of the event is always the same and does not depends on a particular event: If cond is None, then we do nothing special if cond is Some newBehavior then we replace the current Behavior by newBehavior.

let rec colorB =
   let cond t = if (t<10.0)
                then None
                else let rec blackB = Beh (fun t -> (Black, blackB))
                     Some blackB
   let bf t =  match cond t with
               |None -> (White, colorB)
               |Some (Beh newColorB) -> newColorB t
   Beh bf

let r = run colorB s
One more step. Looking at cond, we see that it only depends on time. There is no particular reason to keep it defined within the definition of colorB. It could be passed as a parameter.
// val createColor : (Time -> Color Beh option) -> Color Beh

let rec createColor cond =
   let bf t = match cond t with
              |None -> (White, createColor cond)
              |Some (Beh newColorB) -> newColorB t
   Beh bf

// val cond : float -> Color Beh option
let cond t = if (t<10.0)
           then None
           else let rec blackB = Beh (fun t -> (Black, blackB))
                Some blackB

let colorB = createColor cond

let r = run colorB s
The next step is more fundamental. The cond function depends on time. But we already have things that depends on time, namely Behaviors. So why cond could not be a Behavior? If fact, cond can well become a Behavior. One big advantage of this is that cond functions may have internal state, just like any Behavior.
// -- cond becomes a behavior

let rec condB =
   let bf t = if (t<10.0)
              then (None, condB)
              else let rec blackB = Beh (fun t -> (Black, blackB))
                   (Some blackB, condB)
   Beh bf

Adapting createColor is rather easy.

// val createColor : Color Beh option Beh -> Color Beh

let rec createColor (Beh condf) =
   let bf t = match condf t with
              |(None, ncond) -> (White, createColor ncond)
              |(Some (Beh newColorB), ncond) -> newColorB t
   Beh bf

let colorB = createColor condB

let r = run colorB s
It is still possible to increase the abstraction level. Up to now createColor explicitly depends on the value White. But taking a closer look to what we want, we can conclude that colorB follows the rules:
  • Before some time t0 (10 seconds here) colorB is equal to a constant Behavior whose value is White.
  • After that time, colorB should be equal to the Behavior blackB.
The switchB function captures the essence of what we want: switchB takes a Behavior as first argument and a condition Behavior as second. switchB returns a Behavior that is equal to its first argument until the condition Behavior returns some new Behavior. At this point, the initial Behavior is replaced by the new one.

// val switchB : 'a Beh -> 'a Beh option Beh -> 'a Beh

let rec switchB (Beh bfInit) (Beh condf) =
   let bf t = match condf t with
              |(None, ncond) -> let (rInit, nBInit) = bfInit t
                                (rInit, switchB nBInit ncond)
              |(Some (Beh newBehavior), ncond) -> newBehavior t
   Beh bf

let rec whiteB = Beh (fun t -> (White, whiteB))

let colorB = switchB whiteB condB

let r = run colorB s

In the switchB signature, a quite complex type appears: 'a Beh option Beh . For the sake of clarity and to better discriminate between Behaviors and Events, a specific type is introduced for events:
// definition of event

type 'a Event =  Evt of (Time -> ('a option  * 'a  Event))

And the switchB function now becomes:
// val switchB : 'a Beh -> 'a Beh Event -> 'a Beh

let rec switchB (Beh bfInit) (Evt condf) =
   let bf t = match condf t with
              |(None, ncond) -> let (rInit, nBInit) = bfInit t
                                (rInit, switchB nBInit ncond)
              |(Some (Beh newB), ncond) -> newB t
   Beh bf

Here we are. In a next post I will present combinators and types to create various Events.

Wednesday, March 18, 2009

Functional Reactive Programming in F# (3)

In the previous post, I showed how it was possible with the so-called residual state machine to implement a pure function that maintains a internal state. In this post I will apply this technique to the behaviors discussed in my first post on functional reactive programming. First, let's recall what a Behavior is:

#light

type Time = float

type 'a Beh  = Beh of (Time -> 'a)
To add the possibility to manage state, such a Behavior may be simply transformed into the new type below:
#light

type Time = float

type 'a Beh  = Beh of (Time -> ('a * 'a Beh))

Its associated runList evaluator is an exact copy of the one defined for a state machine.
// val runList : 'a Beh -> Time list -> 'a list

let rec runList (Beh bf) times =
   match times with
   |[] -> []
   |h::t -> let (r, nb) = bf h
            r :: runList nb t
Simple Behaviors, that are independent of any state, are then easy to implement:
let rec doubleB =
    let bf t = (2.0 * t, doubleB)
    Beh bf

let rec twoB =
   let bf t = (2, twoB)
   Beh bf

let rec timeB = Beh (fun t -> (t, timeB))
The following function is constB, similar to constB described in the first post. It takes a value and transforms it into a Behavior that always returns that value, whatever the time.

Two equivalent implementations are possible.

The first possibility makes constB explicitly recursive:

// val constB : 'a -> 'a Beh

let rec constB v =
   let bf t = (v, constB v)
   Beh bf

The second creates a non recursive constB and requests the inner bf function to be recursive.
let constB v =
   let rec bf t = (v, Beh bf)
   Beh bf
As far as my experience tells me, the choice between these two possibilities is left free to the developer.

The lifting functions for our new Behaviors are also quite similar to the old ones.

// val liftB : ('a -> 'b) -> 'a Beh -> 'b Beh

let rec liftB f (Beh bf1)=
    let bf t = let (r1, nb1) = bf1 t
               (f r1, liftB f nb1)
    Beh bf

// val lift2B : ('a -> 'b -> 'c) -> 'a Beh -> 'b Beh -> 'c Beh

let rec lift2B f (Beh bf1) (Beh bf2)=
    let bf t = let (r1, nb1) = bf1 t
               let (r2, nb2) = bf2 t
               (f r1 r2, lift2B f nb1 nb2)
    Beh bf

The next function is a good example of how function may be created by simple composition of other functions. The function makeB takes a function from a time to some type 'a and returns the (state independent) Behavior that implements this function.
//val makeB : (Time -> 'a) -> 'a Beh

let makeB f = (liftB f) timeB

As a comparison, here is the same makeB function implemented the usual way.
let makeB f =
   let rec bf t = (f t, Beh bf)
   Beh bf
Now, what comes is an example of Behavior that manages state. Suppose that we have a function that is passed a state in addition to a time variable, makeWithStateB is a combinator that transform that function into a Behavior.
// val makeWithStateB : ('state -> Time -> 'a * 'state) -> 'state -> 'a Beh

let rec makeWithStateB f (previousState:'state) =
 let bf t = let (a1, nextState) = f previousState t  // call f with the previous state
            (a1, makeWithStateB f nextState)         // pass the next state, returned by f to the next Behavior
 in Beh bf
Here is a simple example that returns the delta between the current time and a previous base time. Everytime the delta reaches 10, the delta is reset to zero and the current time becomes the new base time.
let f t0 t = if (t-t0 < 10.0)
            then (t-t0, t0)
            else (0.0, t)


let times = Seq.to_list (seq { for i in 0 .. 100 -> float i })

let r = runList fB times

Sunday, February 15, 2009

Quicksort in F# (again)

Here is the quicksort algorithm in F#. Nothing new here, this algorithm can be found on many sites. But I noticed that none of them takes advantage of partial application of (<) and (>=) operators in List.filter.

#light

let rec quicksort l =
      match l with
      |[] -> []
      |h::t -> quicksort (List.filter ((<) h) t) @ [h] @ (quicksort (List.filter ((>=) h) t))

let l = [8;2;10;5;3;6;12;23;1;2;5;11]

quicksort l

Saturday, February 14, 2009

Functional Reactive Programming in F# (2)


In my previous post about Functional Reactive Programming, we have seen how a continuous function of time could be implemented in F# (Behaviors) and how it was possible to create more complex Behaviors by combining simpler Behaviors. However, such Behaviors are in fact 'pure' functions of time, without any state. In this post, we will see how Behaviors can handle state in a functional way (without side effects). We start by considering a very simple state machine that consumes unit values () and produces a succession of boolean values: true, false, true, false... Let's start with a classic, imperative implementation:

#light

type 'a StateMachine = unit -> 'a


let TogglingMachine =
     let state = ref true
     let bf evt = state := not (!state)
                  !state
     in (bf :bool StateMachine)

let eventList = [(); (); (); ()]

let r = List.map TogglingMachine eventList
Here, a state machine that produces results of type 'a is simply represented as a function from unit to 'a. Here is a second example. The next machine accepts a unit option as input value and returns a result which is defined as follows:
  • If the input value is None then the machine returns -1.
  • If the input value is Some() then the machine returns the number of None received since the last Some().

type 'a StateMachine = unit option -> 'a


let CountingMachine : int StateMachine =
 let nbNone = ref 0
 let bf evt = match evt with
              |None ->   nbNone := !nbNone + 1;
                         -1
              |Some _ -> let res = !nbNone;
                         nbNone := 0;
                         res
 in bf

let eventList = [None; None; Some(); None; Some(); Some(); None]

let r = List.map CountingMachine eventList

In both examples above, we see that the machine needs to retain some state between two invocations and it does it with the help of some side effects (ref 0 and ref true). There are several solutions to create state machines without side effects. The general idea is to design a machine that externalizes its state. In practice, that means:
  • Its state should be given as an additional input argument.
  • The machine produces a result that, in addition to itsexpected output, contains its new state.
Let's illustrate this with the previous example (the CountingMachine above). First, we have to modify the type representing the machine. It is now a function that takes 2 arguments. The first one is the previous state of the machine (the state before the call) and the second is the usual unit option value. The state is simply the current count of None values. This function returns a pair made of the count of None as explained above and the new state of the machine after the call.

type StateMachine = int -> unit option -> (int * int)


let CountingMachine : StateMachine =
     let bf previousCount evt =
          match evt with
          |None ->  (-1, previousCount+1)
          |Some _ -> (previousCount, 0)
     in bf

It is now the responsibility of the caller to make sure that the right state is passed to the Machine. For this, we can define a runList function which runs the machine against a list of inputs.

let rec runList previousCount machine events =
    match events with
    |[] -> []
    |event::t -> let (res, nextCount) = machine previousCount event
                 nextRes :: runList nextCount machine t

let r = runList 0 CountingMachine eventList


We see clearly the drawbacks of such a solution. The runList function must be aware of two things:
  • The first, as already mentionned, is the handling of the state. Unfortunately, in this solution and in the next solution (a little bit below), this cannot be avoided.
  • The other drawback is the dependency of runList on the type of the state - int in this case. Thus, every Machine designed on state externalization needs its own runList function.
  • A third drawback, a bit less obvious at first sight, is the fact that the state must always be of the same type across several calls. It is not possible to replace, from one call to another, such a Machine with another that has a state of a different type.
Of course, the type for the machine presented above may be made generic:

type StateMachine<'a, 'state> = 'state -> unit option -> ('a * 'state)
Last solution, based on residual state machines. This solution is based on a simple fact. Since a State Machine is basically a function of one argument, let's imagine that this function returns both its expected value and new State Machine. This a new State Machine acts a bit like the state in the previous example. The type of such a machine is:

type 'a StateMachine = SM of (unit option -> ('a * 'a StateMachine))

We can already define some simple state machines: A machine that always returns true. Two implementation are possible, depending on which definition is recursive.

let AlwaysTrueMachine = let rec bf evt = (true, SM bf)
                        SM bf


let rec AlwaysTrueMachine = let bf evt = (true, AlwaysTrueMachine)
                            SM bf

The Toggling Machine in the beginning of this post becomes.

let TogglingMachine = let rec bf previous evt = (previous, SM (bf (not previous)))
                      SM (bf true)

To be able to run these machines, we must again define a runList function:

let rec runList (SM bf) events =
       match events with
       |[] -> []
       |h::t -> let (r, nb) = bf h
                 r :: runList nb t

let r = runList TogglingMachine eventList

This runList function is somewhat similar to the one already defined above but with 2 advantages:
  • It does not depend on the way the state machine models its state (or not - see the AlwaysTrueMachine which has no state at all).
  • As a consequence, a state machine may well change its state representation at will. The only condition is that the values it produces must have the same type.
So we come to the end of this post. As a last note, I must admit that there could be another way to model state machines, which is based on sequences but I have not explored this direction yet. In a next post, I will make the connection between state machines and Behaviors.