Sunday, July 1, 2012

Understanding variance using functions

Statically typed languages that support parametrized types (generics) and types hierarchies (inheritance) sometimes support covariance and contravariance, concepts which many find confusing.

I think I have finally understood these, thanks to a blog post by Tomas Petricek on the subject.

In this post I'll try to formulate my own understanding, and how I got there using functions instead of classes.

Step 1: values

Let us start easy, with simple values. Consider a base type, for instance IPrintable, and two derived types MyString and MyInt.

I can use a string with any function that accepts a printable object.

type IPrintable =
    interface
    end

type MyInt() =
    interface IPrintable

type MyString() =
    interface IPrintable

// Step 1: simple value
let ``expects an IPrintable``(x : IPrintable) = ()

let n = MyInt()
let s = MyString()

``expects an IPrintable`` n // OK
``expects an IPrintable`` s // OK

Step 2: Parameterless functions

The next step deals with a function that takes another function which doesn't take any parameter and returns an IPrintable. If that's confusing, think of a generic function that creates a new random printable object, then prints it. This function would let the caller be responsible for providing a function which creates the random printable object.

The code below illustrates this, but I've removed the random part. Note also that F# does not support covariance, which forces me to use flexible types.

// Step 2: a function without arguments
// No covariance in F#, see http://msdn.microsoft.com/en-us/library/dd233198.aspx
let ``expects a constructor``(f : unit -> #IPrintable) = ()

let mkInt() = MyInt()
let mkString() = MyString()

``expects a constructor`` mkInt // OK
``expects a constructor`` mkString // OK

Step 3: Functions of a single parameter

Let us now consider a variation of the function described above where the function responsible for creating a random object takes a MyInt (it could be the seed, for instance). Assume I have two functions newRandomMyIntWithSeed and newRandomMyStringWithSeed that both take an IPrintable. Importantly, these two functions are safe to call with any instance of IPrintable. One can imagine that such a function would use the printable representation to generate some number, used as the seed for the random generator.

I can use newRandomMyIntWithSeed and newRandomMyStringWithSeed where a function with signature MyInt -> IPrintable is expected. Notice how the relationship on types for the parameter has been inverted, compared with the case of a value or a return type. This is an example of contravariance.

No code here, but see below for a more complete example.

Step 4: Functions of multiple parameters

It's possible to keep adding more parameters, and currying helps understand which functions are safe to use.
For this last example, I'll switch to another set of types: IScalar and IVector, with their respective implementations Float32 and Vector3. We can imagine there might be other implementations, e.g. Float64 and Vector4. A function which computes the product of a scalar and a vector must return a vector. Using currying, it can also be seen as a function takes a scalar and returns a function which takes a vector and returns a vector.

If I have a function with signature Float32 -> Vector3 -> Vector3, where can I use it?

I can use it where the exact same signature is expected, obviously.

I can use it where a Float32 -> Vector3 -> IVector is expected:
  • The final return types match, as shown in step 1.
  • The other parameters obviously match.
I cannot use it where a Float32 -> IVector -> Vector3 or a Float32 -> IVector -> IVector is expected. Although the final return types are compatible in either case, the next step in the matching process fails.

A more general function with signature IScalar -> IVector -> Vector3 can be used where a Float32 -> Vector3 -> IVector is expected:
  • Vector3 as a simple value can be used anywhere any IVector is expected.
  • A function accepting any IVector accepts in particular Vector3, meaning such a function can be used where a function expecting a Vector3 is expected (!), provided their return types match (which was shown above).
  • By the same reasoning applied on the first (and only) argument of the function with signature IScalar -> (IVector -> Vector3), we conclude that the more general function can be used.
The code below illustrates this example.

// Step 4: a function with arguments
type IScalar =
    interface
    end

type IVector =
    interface
    end

type Float32() =
    interface IScalar

type Vector3() =
    interface IVector

let prodGeneral (s : IScalar) (v : IVector) : Vector3 =
    failwith "..."

// Interesting: flexible types are needed for the return type (no covariance),
// but not for the parameters (contravariance)
let apply prod (s : Float32) (v : Vector3) : #IVector = prod s v // OK

let k = Float32()
let v = Vector3()
let u = apply prodGeneral k v

Conclusion

I hope that wasn't excessively complex. Other explanations on the subject which I have seen often use container classes instead of functions, which is confusing, as it brings in read-only vs writable and reference-type vs value-type into the picture. Another problem is that using containers tends to mislead readers into thinking that T<B> can always be used where T<A> is expected if B inherits from A. Although that makes sense when T is IEumerable, it doesn't work when T is Action.
Looking at the problem with a functional mindset really helped clarify the picture.

I was a bit disappointed when I first saw F# did not support covariance, but flexible types do the job with very little additional syntax (a single # before the type). I was surprised to notice F# does support contravariance for function parameters, as it's often heard that F# supports neither covariance nor contravariance. That's not quite true, as it turns out.

If functions are powerful enough to model all other types, it may be interesting to see what kind of variance one should expect for unions, tuples, records and eventually classes. That's probably already been done, but it would be an interesting exercise.

Tuesday, June 26, 2012

Recursive descent parsers using active patterns, part 2

In the previous post, I presented a method to implement a parser relying solely on core F# features, namely active patterns.
In this post, I'll touch on some of advantages and limits of this approach.
Recursive descent parsers are limited to LL(k) grammars, which means that left-recursive grammars cannot be directly handled. It is necessary to rewrite such grammars to remove left recursion.

Consider the common problem of parsing expressions, e.g. Boolean expressions. A typical formulation of the  grammar could be:

Expr := AndExpr | OrExpr | NegExpr | Variable | True | False | "(" Expr ")"
AndExpr := Expr "AND" Expr
OrExpr := Expr "OR" Expr
NegExpr := "~" Expr | Expr

Note there is an ambiguity, as "A AND B OR C" could be parsed as (A AND B) OR C or as A AND (B OR C). In order to lift this ambiguity, priorities can be assigned to rules. Similarly for associativity, allowing to parse "A AND B AND C" as (A AND B) AND C or A AND (B AND C).

Such a grammar, if implemented naively using a recursive descent parser, would loop endlessly on some inputs: The parser would try to match rule AndExpr, which would try to match Expr, which would again try to match AndExpr...

An alternative formulation of the grammar can be used that will generate semantically equivalent results

Expr := OrExpr
OrExpr := AndExpr "OR" OrExpr | AndExpr
AndExpr := NegExpr "AND" AndExpr | NegExpr
NegExpr := "~" AtomExpr | AtomExpr
AtomExpr := Variable | True | False | "(" Expr ")"

Note the hierarchy between Expr, OrExpr, AndExpr, NegExpr and AtomExpr. The left-most rule appearing on an alternative in the right-hand side of each definition is always a "lower" rule: Expr refers to OrExpr, OrExpr to AndExpr, AndExpr to NegExpr, NegExpr to AtomExpr.
AtomExpr refers to the higher rule Expr in "(" Expr ")", but that's OK as Expr does not appear as the left-most rule (the token for a left parenthesis does).

What I like with this formulation is that it captures both associativity and operator precedence within the system of rules.

It is common to split parsers into two stages, using a lexer that processes the input stream in linear time, producing a pre-digested stream of so-called tokens. While this has undeniable advantages when it comes to performance, it prevents composing grammars and rule-specific tokenization. This is why most languages have keywords reserved for future use, and this also explains why you can't use identifiers that are also keywords even in situations where no ambiguity arises.

For these reasons, I personally prefer avoiding the separate lexing stage if performance constraints allow for it.

Regarding performance, it's important to write a recursive descent parser in such a way that decisions on the rule to try can always be done looking at a finite number of tokens.

In the example below, the second implementation performs significantly better:

let (|OrExpr|_|) s =
  match s with
  | AndExpr (e1, Token ("OR", OrExpr(es, s))) -> Some (e1 :: es, s)
  | AndExpr (e, s) -> Some ([e], s)
  | _ -> None
let (|OrExpr|_|) s =
  match s with
  | AndExpr (e1, s) ->
    let rec work s es =
      match s with
      | Token ("OR", AndExpr(e, s)) -> work s (e :: es)
      | _ -> (List.rev es, s)
    let es, s = work s []
    Some(e1 :: es, s)
  | _ -> None

To see what happens, consider the input "~X". This is a "degenerate" OrExpr with a single term. The first implementation will go all the way down through each rule to identify a NegExpr, promoting it to an AndExpr, then will look for "OR", which isn't there. The first match case will therefore fail, and the second will be tried, redoing the work. The same problem exists at all levels in AndExpr, NegExpr and AtomExpr. What makes matters worse is that this kind of "degenerate" case is actually the normal common case in typical expressions.

The second implementation uses the functional equivalent of a while loop, going as far as possible. The trick here is to factorize common prefixes into a single branch, thus avoiding redoing the work in case of a match failure.

An important problem with my simple example code is the lack of error messages. Those are important from a usability point of view, but I'm currently not too sure how to do this with manually-written parsers.

To summarize, using this technique requires some amount of manual work, which is the price to pay for not using smarter parsing frameworks. I wouldn't advise it over using parser generators, but it's interesting nonetheless. I can see it having uses for extremely small grammars, for instance when parsing fragments in a document. Otherwise, go for a parser generator such as fslex+fsyacc or ANTLR (which generates recursive descent parsers), or combinator-based parsers such as FParsec.

Friday, May 18, 2012

Recursive descent parser using active patterns

Today's post isn't specifically about games, but about parsing, which I find is a recurring task in many programming tasks, including game-related tasks.

In F#, the most popular methods for writing parsers are FParsec and fslex/fsyacc. Although parser generators are very useful, I'm always a bit reluctant to depend on third-party software.

In the past I have worked on a development tool for safety-critical systems, which was itself subject to some of the limitations of software for safety-critical systems. In particular, the use of lex and yacc was not accepted.

I fell back on a technique suitable for hand-written parsers, namely recursive descent parsers. I was positively surprised by the inherent simplicity of the method and the clarity of code that resulted.

I was first exposed to the idea of using active patterns for parsing when I read a blog post by Jon Harrop.
Active patterns is a feature specific to F#, and the F# wikibook has a chapter dedicated to them. I'll be using parameterized partial active patterns.

We start by defining a type for the input. The integer denotes the number of lines read so far, the list of strings is the input split at line-breaks.
open System.Text.RegularExpressions

type Stream = Stream of int * string list

A pattern to detect the end of the input, when the list of strings is empty.
let (|EOF|_|) = function
    | Stream(_, []) -> Some()
    | _ -> None

A pattern to detect end-of-lines, by recognizing list of strings which start with the empty string.
let (|EOL|_|) = function
    | Stream(n, "" :: rest) ->
        Some (Stream(n + 1, rest))
    | _ -> None
This pattern eats white space.
let (|OneWS|_|) = function
    | Stream(n, line :: rest) ->
        let trimmed = line.TrimStart()
        if trimmed <> line then
            Some (Stream(n, trimmed :: rest))
        else
            None
    | _ -> None
A convenient pattern to eat sequences of white space and newlines. Note the use of the rec keyword, which allows to refer to the pattern itself in its implementation.
let rec (|WS|_|) = function
    | OneWS (WS s)
    | EOL (WS s) -> Some s
    | s -> Some s
We could also have attempted another variant, where WS uses itself for the first part, which would implement a left-recursive grammar. Unfortunately, this pattern would be useless, as all it would do is raise stack-overflow exceptions.
let rec (|WS1|_|) = function
    | WS1 (OneWS s) -> Some s
    | s -> Some s
My variant of the Regex pattern differs a bit from the one in the wikibook, to avoid re-building Regex objects, which has a non-neglectable cost.
let (|Regex|_|) (regex : Regex) = function
    | Stream(n, line :: rest) ->
        let m = regex.Match(line)
        if m.Success then
            let lineRest = line.Substring(m.Length)
            let values =
                [ for gr in m.Groups -> gr.Value ]
            Some (values, Stream(n, lineRest :: rest))
        else None
    | _ -> None
A sample pattern to illustrate the use of the Regex pattern.
let personRegex = Regex("NAME: (\w+) AGE: (\d+)")
let (|Person|_|) = function
    | WS (Regex personRegex ([_ ; name ; age], s)) -> Some ((name, age), s)
    | _ -> None
A pattern to parse data of a large number of persons. I could have used recursion at the level of the pattern itself, similarly to WS. However, such a pattern would not be tail-recursive, and would cause stack overflows for large numbers of entries.
let (|Persons|_|) s =
    let rec work s persons =
        match s with
        | Person (p, s) -> work s (p :: persons)
        | _ -> (persons |> List.rev, s)
    let persons, s = work s []
    Some (persons, s)
Finally, some utility code to initialize streams, generate one million lines to parse, followed by the parsing itself.
let streamOfLines lines =
    Stream(0, lines |> List.ofSeq)

let streamOfFile path =
    Stream(0, System.IO.File.ReadAllLines(path) |> List.ofArray)

let stream =
    seq { for n in 0..1000000 do
            yield sprintf "  NAME: Anonymous AGE: %d              " (n % 99) }
    |> streamOfLines

#time "on"
match stream with
| Persons (p, WS EOF) -> printfn "Success %A" p
| _ -> printfn "Failed"
#time "off"
Parsing takes about 9 seconds on my PC (18s if I recreate the Regex object repeatedly). I think that's very decent performance.
In a future post, I'll describe how to parse Boolean formulas and expand a bit on the power and performance of this method.

Tuesday, May 1, 2012

Problems with portable libraries and object-oriented APIs

I've got along well with inheritance for a long time, but this was not peace. Inheritance was preparing, in the dark, cowardly, waiting to byte me. And it just did that!

In my last post, I presented a method to detach libraries from external assemblies and let applications take responsibility for the "linking".

The key was to use interfaces to shadow the API of the external assemblies. Sadly, it falls apart when the API being shadowed, say XNA, relies on inheritance to connect to the user's code.

Take GameComponent, for example. Users are expected to define a type that inherits from GameComponent, overriding a number of methods (Initialize, Update and Draw, typically).

It would be nice if one could declare that XNA provides a type GameComponent with abstract methods (the syntax is made up, that's not valid ML or F#):
signature Xna =
  type GameTime
  type GameComponent with
    abstract new : unit -> unit
    abstract Initialize : unit -> unit
    abstract Update : GameTime -> unit
    abstract Draw : GameTime -> unit

Using the method described in the previous post, this would become in F#:
type XnaImplementation<'GameTime, 'GameComponent>() =
  ...

Then F# code could maybe do something like that:
type MyGameComponent<'GameTime, 'GameComponent>(xnaOps : XnaImplementation<'GameTime, 'GameComponent>) =
  inherit 'GameComponent()
  ...

That is however not valid F# code, as inheriting from generic types is not allowed.
I have a solution for that in my code, but I'm not very happy. It involves a new interface IGameComponent that the API provider has to wrap inside XNA's GameComponent.
Throw into the lot that XNA's GameComponent provides some functionality (properties Visible and Enabled) that MyGameComponent needs to be able to access, and you need to throw another wrapper into the picture. Not pretty at all.

I've been considering whether I should take a different approach and create a so-called reference assembly for XNA. In theory, it shouldn't be hard. Extract the type definitions and methods that are needed from the actual libraries, put them into a reference assembly, and be done with it. Unfortunately, there does not seem to be a tool to do that available to the public. Microsoft should seriously consider including such a tool with VS11, it would allow users to add the little bits that were not portable enough for the portable .NET core, but that are nevertheless available on the platforms that users are targeting.

There are days when I really miss SDL. A simple library that lets itself be called, but doesn't call you. Lesson of the day: object-oriented APIs without proper tooling are painful.

Monday, April 30, 2012

Modular programming for portable F# libraries

I've been battling a few more rounds with F# portable class libraries. Getting them to work on PCs wasn't a walk in the park, but it seems I've got it working at last. Although this particular problem is not the main topic of this post, I expect many will run into the same issue, so I'll dedicate a few lines to its resolution.

The setting

I have a portable F# library which performs some physics calculations. Typical stuff you would expect in a portable library. It's unimaginatively but aptly named PortableLibrary1.
There is also an F# application project to run the simulation in a windows console (as in "text console", no xbox fun involved at this stage yet) application.
The application project refers to the library project.

The problem

The application compiles fine, but crashes when run with an exception stating that some version of FSharp.Core.dll could not be loaded.

The solution

Insert the following lines into the app.config file in the application's project:

<runtime>
  <assemblyBinding xmlns="urn:schemas-microsoft-com:asm.v1">
    <dependentAssembly>
      <assemblyIdentity name="FSharp.Core" publicKeyToken="b03f5f7f11d50a3a" culture="neutral"/>
      <bindingRedirect oldVersion="2.3.5.0" newVersion="4.3.0.0"/>
    </dependentAssembly>
  </assemblyBinding>
</runtime>

Thanks to Brian and his answer on stackoverflow.

We can run portable code on the PC, but the problems I mentioned in my previous post are still there, namely:

  1. I can't reference functions and types from Microsoft.Xna.Framework because there is no portable version (that I know of).
  2. There are core functions that are not available in the portable core, e.g. Thread constructors.

I will show below a solution to these two problems (my apologies to all bird lovers out there).

Signatures and modules

F# has its origins in ML, and some ML languages (standard ML, Ocaml) offer a module system that separates interfaces (which are called signatures) and implementations (call structures). Unfortunately, the module system of F# isn't as powerful. It's probably difficult, if not impossible, to fully emulate modules in F#. Nevertheless, there may some nice aspects of ML modules that can be imitated in F#.
  • The module system distinguishes interfaces and implementations.
  • Signatures specify a number of related types and operations operating on them in an abstract way.
  • Structures provide a number of concrete types and functions satisfying the specification in the structure they implement.
A signature of vector math could look as shown below:

signature VectorMath
  type V
  val add: V * V -> V
  val dot: V * V -> float32
  val len: V -> float32

In the .NET world, there is something that might play the role of signatures, namely interfaces. The problem is how to express that module VectorMath should have a type V? Interfaces can be used to specify operations, but not nested types. In my solution, I have used generics:
type VectorMath<'V> =
    interface
        abstract Add : 'V * 'V -> 'V
        abstract Subtract : 'V * 'V -> 'V
        abstract Dot : 'V * 'V -> float32
        abstract Scale : float32 * 'V -> 'V
        abstract Len : 'V -> float32
        abstract Len2 : 'V -> float32
        abstract Zero : 'V
        abstract AreEqual : 'V * 'V -> bool
    end

Note that the dimension of the vector type V is not constrained. This signature allows to perform interesting operations on vectors regardless of whether we are working in 2d or 3d.
Operations that depend on the number of dimensions are found in additional signatures:
type Vector2Math<'V> =
    interface
        inherit VectorMath<'V>
        abstract Cross : 'V * 'V -> float32
        abstract UnitX : 'V
        abstract UnitY : 'V
        abstract Create : float32 * float32 -> 'V
    end

type Vector3Math<'V> =
    interface
        inherit VectorMath<'V>
        abstract Cross : 'V * 'V -> 'V
        abstract UnitX : 'V
        abstract UnitY : 'V
        abstract UnitZ : 'V
        abstract Create : float32 * float32 * float32 -> 'V
    end

Modules implementing these signatures are written using any .NET type that can implement interfaces. In F#, discriminated unions do the job. As a side note, I tend to use single-discriminant DUs a lot in my F# code. I see them as C's typedefs the way they should have been.
type XnaVector3Math =
    | XnaVector3Math
    interface PortableLibrary1.Vector3Math<Vector3> with
        member this.Add(v1, v2) = v1 + v2
        member this.Subtract(v1, v2) = v1 - v2
        member this.Scale(x, v) = x * v
        member this.Dot(v1, v2) = Vector3.Dot(v1, v2)
        member this.Cross(v1, v2) = Vector3.Cross(v1, v2)
        member this.Len(v) = v.Length()
        member this.Len2(v) = v.LengthSquared()
        member this.AreEqual(v1, v2) = v1 = v2
        member this.UnitX = Vector3.UnitX
        member this.UnitY = Vector3.UnitY
        member this.UnitZ = Vector3.UnitZ
        member this.Zero = Vector3.Zero
        member this.Create(x, y, z) = new Vector3(x, y, z)

Keep in mind the problem I wanted to solve was how to remove the dependency on the XNA dll from the portable library. The interfaces are part of the portable library, the implementation is in the application's code.
The same method can be used to send missing bits of Thread from the application (which has access to the missing bits) to the portable code.

Using signatures

The code for the physics simulation is shown below, not so much for its value as a physics engine, but to judge of the usability of signatures.
type SystemState<'V> =
    { mass : float32[]
      pos : 'V[]
      speed : 'V[] }

let computeForces (ops : #VectorMath<'V>) state =
    let forces =
        [|
            for mass, pos in Array.zip state.mass state.pos do
                let force =
                    Array.zip state.mass state.pos
                    |> Array.map (fun (mass', pos') ->
                        if ops.AreEqual(pos, pos') then
                            ops.Zero
                        else
                            let relPos = ops.Subtract(pos', pos)
                            let dist = relPos |> ops.Len
                            ops.Scale(mass * mass' / (dist * dist * dist), relPos))
                    |> Array.fold (fun x y -> ops.Add(x, y)) ops.Zero
                yield force
        |]

    forces

let update (ops : #VectorMath<'V>) dt state =
    let inline (.*) k v = ops.Scale(k, v)
    let inline (.+.) v1 v2 = ops.Add(v1, v2)

    let forces = computeForces ops state
    let accels =
        Array.zip state.mass forces
        |> Array.map (fun (mass, force) -> (1.0f / mass) .* force)

    let speeds =
        Array.zip state.speed accels
        |> Array.map (fun (speed, accel) ->
            speed .+. (dt .* accel))

    let positions =
        Array.zip state.pos speeds
        |> Array.map (fun (pos, speed) ->
            pos .+. (dt .* speed))

    { state with
        pos = positions
        speed = speeds }

let initialize (ops : #Vector3Math<'V>) =
    let rnd = new System.Random(0)
    let nextFloat() = rnd.NextDouble() |> float32

    let N = 1000

    let masses =
        Array.init N (fun _ -> nextFloat() * 1000.0f)

    let positions =
        Array.init N (fun _ ->
            let len = nextFloat() * 100.0f
            ops.Scale(len, ops.Create(nextFloat(), nextFloat(), nextFloat())))

    let speeds =
        Array.init N (fun _ -> ops.Zero)

    { mass = masses
      pos = positions
      speed = speeds }

let centerOfMass (ops : #VectorMath<'V>) state =
    let wpos =
        Array.zip state.pos state.mass
        |> Array.map (fun (pos, mass) -> ops.Scale(mass, pos))
        |> Array.fold (fun wpos x -> ops.Add(wpos, x)) ops.Zero

    let mass = Array.sum state.mass
    
    ops.Scale(1.0f / mass, wpos)

Discussion

This approach has a number of problems, compared with traditional F# modules.
  1. Additional level of indirection when calling operations. In performance-critical situations, this can matter.
  2. Additional ops parameter sprinkled in all functions that use the signature. A bit tiresome to write. Call sites aren't as badly affected, thanks to partial application and currying.
  3. Need to specify the signatures. Will I need to duplicate all of XNA's API in signatures?
There are a number of non-problems, i.e. problems that have pretty good solutions:
  1. Operator overloading: See update for an example on how to use operators to improve the look of expressions involving vector math.
  2. Callers need not pass ops explicitly at each call site, as shown below:
In the library:
let mkModule ops =
    (fun () -> initialize ops),
    update ops,
    centerOfMass ops

In the application:
let initialize, update, centerOfMass = PortableLibrary1.mkModule MyVector3Math
let state = initialize()
let center0 = centerOfMass state

The benefits include:
  1. Truly write-once-run-everywhere library code. I should be able to use my library code in a game for Sony devices using the Playstation Suite SDK, or for smart phones (actually, not quite, due to limitations regarding generic virtual methods in Mono).
  2. Looser coupling between libraries. It's up to the top level, the application, to specify implementations. That's the right thing to do, since that's the only part that should be aware of the target platform and its  specifics.
Programmers with a background in OOP might wonder why I did not use an interface for the vector type itself, instead of providing an interface for a module. Note that would not really help me here, as XNA's Vector3 and Vector2 don't implement this interface (of which they know nothing). I would need some bridging type anyway.
Providing abstraction on the module-level, as opposed to the "object" level allows to group related types in a module specification. A more complete vector math signature would include matrices and operations that operate on vectors and matrices. The OOP approach forces these operations into one of the vector and matrix types, which I have always found a bit arbitrary.

Saturday, April 28, 2012

Portable Class Libraries: Are they worth the trouble?

The (initial) problem

Everyone who's been developing games using XNA for the Xbox360, WP7 and the PC platforms knows managing projects and solutions is a bit troublesome. Here is the problem: in theory, all you would need is to have a single solution with three platforms: x86, xbox and wp7.
However, that's not how it works in practice. The various DLLs that you need to reference vary from one platform to the next, meaning you have to create multiple projects for each library. The XNA plugin for Visual Studio helps with the task of managing multiple libraries, but it doesn't work for F# projects.
I have developed a script that generates xbox projects from pc projects, but it's more of a hack than a reliable method. It also requires some amount of manual intervention. Although I am personally relatively satisfied with this solution, I imagine it will be close to no use to anyone but me.

The (supposed) solution

The release of Visual Studio 11 beta has exposed a new type of project: Portable Class Library. Here is what MSDN has to say about them:
Using a Portable Class Library project, you can build portable assemblies that work without modification in .NET Framework, Metro style, Silverlight, Windows Phone 7, and Xbox 360 apps.
That sure sounds interesting. I decided to try this new feature by adopting it for XNAUtils.

The reality (more problems)

No need to maintain the suspense to the end of this post, I can already reveal I'm not positive about these libraries. The rest of this post describes a number of hurdles I have encountered so far.

The screenshots on MSDN don't look like my screen

The MSDN docs state that you can specify which platforms you intend to support. Since each platform has its limitations, limiting support to a number of platforms my allow for larger accessible feature sets.
That's how it's supposed to look. The project properties should have a button "Change" allowing to access the various platforms.

Sadly, that does not apply to F# prjects:

No "Change" button to be seen. Somewhat worryingly, the Xbox platform is not mentioned here.
In any case, I chose to ignore that problem and go ahead...

What kind of libraries can I refer to?

I will need to access at Microsoft.Xna.Framework, and possibly also Graphics. However, those are not available as portable libraries. I referenced the ones for Xbox, and hoped for the best. It might work on the xbox, but I don't see how that could possibly work on the PC?! I haven't come to the point where I could run something, so we'll see how that goes...

Dude, where's my Thread constructor?

One of my functions creates a thread. This code no longer compiles, I have posted a question on stackoverflow on the subject.
Summary: Apparently, the constructor I want to use is not available in portable class libraries, despite the MSDN doc claiming the contrary.
That's not very reassuring. Deciding whether to take the step to PCLs requires some thinking ahead, and the information available from official sources isn't reliable. I know it's still a beta release, but it's unpleasant nevertheless.
There is a feeling of deja-vu with this one. Back in the days when I was working on my asteroids clone, I had a problem with the thread class. I had used the PC dlls of XNA in my xbox build. That worked fine before XNA 3.1, but there was a catch. The code would compile, but crash when run on the xbox. The offender was a method of Thread that was not available on the xbox.
The solution consisted of wrapping the correct method in a delegate in the top-level C# code, and send it down to my F# code, which could invoke it to perform the required operation.
It seems I will have to use the same trick here if I want to be able to create threads. The portable framework doesn't allow creating threads, but the XNA framework, which "implements" the portable framework, has the constructor I need. A solution would therefore be to get the thread constructor from the top-level app (which is aware of the specific platform it will run on) and pass it down to the portable code.
This solution should be usable for any "non-portable" functionality that you know exists on the platforms you target.

Conclusion

The experiment is not conclusive yet, as I haven't gotten to the point where I can run things. I wonder if it's worth the trouble.
This shows linking to implementations is a mistake. What you should link to is signatures. Then it's up to the top level, the application, to specify a set of implementations which satisfy these signatures. Libraries have no business depending on implementations.
The approach consisting of providing implementations that "work everywhere" is probably not going to work well, since they are very likely to lack basic functionality that isn't available everywhere in exactly the same way.

Tuesday, February 14, 2012

Units of measure for array indices

In F#, arrays play an important part in optimizing performance-critical parts of your code. This is especially true on Xbox 360, where arrays of value types can help avoid snags due to slow garbage collection. Unfortunately, index out-of-bound exceptions are common when working with arrays. This post shows a little trick to help detect cases where the wrong variable is used as the index.

/// An array whose index has a unit of measure
type MarkedArray<[<Measure>] 'K, 'T> = MarkedArray of 'T[]
with
    member this.Content =
        let (MarkedArray arr) = this
        arr

    member this.First : int<'K> =
        LanguagePrimitives.Int32WithMeasure 0

    member this.Last : int<'K> =
        let (MarkedArray arr) = this
        LanguagePrimitives.Int32WithMeasure (arr.Length - 1)

    member this.Item
        with get (i : int<'K>) =
            let (MarkedArray arr) = this
            arr.[int i]
        and set (i : int<'K>) (v : 'T) =
            let (MarkedArray arr) = this
            arr.[int i] <- v

The interesting bit lies in the definition of this.Item. It allows to access the content of a MarkedArray using the usual array notation arr.[idx]

To illustrate how this is used, imagine you are making an Asteroids clone. You'll probably need arrays for the positions and velocities of the ships (assuming it's a multiplayer game), and similarly for the asteroids. Using units of measures as shown in the previous post will help avoid mixing speeds and positions, but it's still possible to pick a position from the wrong array.

This is the problem that MarkedArray solves, see below.
[<Measure>] type Ship
[<Measure>] type Asteroid

type State =
  { shipPositions : MarkedArray<Ship, TypedVector3<m>>
    shipVelocities : MarkedArray<Ship, TypedVector3<m/s>> 
    asteroidPositions : MarkedArray<Asteroid, TypedVector3<m>>
    asteroidVelocities : MarkedArray<Asteroid, TypedVector3<m/s>> }

let getShipPosition (state : State) (idx : int<Ship>) : TypedVector3<m> =
  state.asteroidPositions.[idx] // Fails: idx has the wrong type, expected int<Asteroid>

Note also that creating marked arrays isn't as tedious as one might fear, thanks to type inferrence
let state' = { state with shipPositions = state.shipPositions.Content |> Array.map f |> MarkedArray }

A small remark to finish off, this is how to iterate over all positions in a marked array, note the 1<Ship> increment:
for idx in state.shipPositions.First .. 1<Ship> .. state.shipPositions.Last do
  ...
By the way, both TypedVector3 and MarkedArray are available in XNAUtils on bitbucket.

Monday, January 16, 2012

Units of measure to the rescue!

Physics can really improve immersion in a game, regardless of how faithful they are to reality. That's why I always enjoyed writing simple physics engine. Even though I have stuck to really simple physics engine, I always end up mixing accelerations and forces. That usually doesn't lead to much trouble in the final result, as masses tend to be constant, and physical properties of game objects are typically chosen after experimentation to maximize fun.

The feeling that there is something wrong with the math in my code is always annoying, though. It turns out F# has a solution for that, called units of measure.

A unit of measure is a type annotation that helps programmers write correct formulas. It's obviously useful for formulas in simulations, whether one is dealing with physics, finances or any other domain where models play an important role.

The code below shows how to declare a unit measure.
/// Position, meters
[<Measure>] type m

/// Time, seconds
[<Measure>] type s

/// Mass, kilograms
[<Measure>] type kg
Units in physics have a certain level of redundancy, one might say. For instance, forces can be expressed in Newtons or in kilograms time meters per squared seconds. Newtons are obviously more convenient to use, but you want that masses multiplied by accelerations be recognized as forces. This is how you capture Newton's law:
/// Force, Newtons
[<Measure>] type N = kg m/s^2
Units of measure can be used with primitive numeric types such as int, float and float32.
let integrateShips (dt : float32<s>) (ships : Ships) ...
dt above denotes a time duration in seconds represented using a 32-bit floating point value. Units of measure can also be applied to complex types. The code below shows the code for a wrapper around Xna's Vector3.
/// A three-dimensional vector with a unit of measure. Built on top of Xna's Vector3.
type TypedVector3<[<Measure>] 'M> =
    struct
        val v : Vector3
        new(x : float32<'M>, y : float32<'M>, z : float32<'M>) =
            { v = Vector3(float32 x, float32 y, float32 z) }
        new(V) = { v = V }

        member this.X : float32<'M> = LanguagePrimitives.Float32WithMeasure this.v.X
        member this.Y : float32<'M> = LanguagePrimitives.Float32WithMeasure this.v.Y
        member this.Z : float32<'M> = LanguagePrimitives.Float32WithMeasure this.v.Z
    end

[<RequireQualifiedAccessAttribute>]
module TypedVector =
    let add3 (U : TypedVector3<'M>, V : TypedVector3<'M>) =
        new TypedVector3<'M>(U.v + V.v)

    let sub3 (U : TypedVector3<'M>, V : TypedVector3<'M>) =
        new TypedVector3<'M>(U.v - V.v)


type TypedVector3<[<Measure>] 'M>
with
    static member public (+) (U, V) = TypedVector.add3 (U, V)
    static member public (-) (U, V) = TypedVector.sub3 (U, V)
This allows to add and subtract vectors with compatible units of measure. It took me some effort to figure out how to handle multiplication by a scalar. First, in module TypedVector:
let scale3 (k : float32<'K>, U : TypedVector3<'M>) : TypedVector3<'K 'M> =
        let conv = LanguagePrimitives.Float32WithMeasure<'K 'M>
        let v = Vector3.Multiply(U.v, float32 k)
        new TypedVector3<_>(conv v.X, conv v.Y, conv v.Z)
Then the type extension:
type TypedVector3<[<Measure>] 'M>
with
    static member public (*) (k, U) = TypedVector.scale3 (k, U)
Note the use of LanguagePrimitives.Float32WithMeasure<'K 'M> to produce a number with a specific unit of measure in a generic fashion.

I have designed the class to reuse Xna's implementation although it wouldn't have been hard to write my own from scratch. The key benefit, on Windows Phone 7, is to take advantage of some fast vector math that's only accessible through Xna's types. The PC and Xbox platforms don't support fast vector math, but who knows, it may come.

Finally, here comes an example of how to use all this:
    let speeds2 =
        Array.map2
            (fun speed (accel : TypedVector3<m/s^2>) ->
                let speed : TypedVector3<m/s> = speed + dt * accel
                speed)
            ships.speeds.Content accels.Content

    let posClient =
        ArrayInlined.map3
            (fun pos speed speed2-> pos + 0.5f * dt * (speed + speed2))
            ships.posClient.Content
            ships.speeds.Content
            speeds2
There is more to be said and written about units of measures, a future post will show how they can be used for safe access of array contents.

Thursday, January 12, 2012

Parallel draw-update XNA game component

Video games are often demanding when it comes to computation power, especially simulations and 3d games. The Xbox 360 has 3 cores with two hardware threads each. Of these 2 are reserved for the system, leaving 4 available to the programmer.
This article describes an easy to use custom XNA game component that allows to run computations in parallel with rendering.

The typical game loop is often divided in two steps, update and draw. I suggest a slightly different workflow divided in three steps, two of which run in parallel: update, compute and draw. The traditional update stage is divided in two new steps, update and compute.

In this new setting, update is used for receiving inputs from the player and the network, in the case of an online multiplayer game. Compute is potentially cpu-hungry operation implemented in a purely functional way. Rendering plays the same role as usual.

The code for the entire component fits in little over 100 lines, see below.
namespace CleverRake.XnaUtils

open Microsoft.Xna.Framework
open System.Threading

type IFramePerSecondCounter =
    abstract FramesPerSecond : float

/// An update-able and drawable game component which performs light updates on the main
/// thread, then draws on a separate thread in parallel of more computation-heavy updates.
/// initialize_fun is called when assets are loaded.
/// dispose is called when the component is disposed, and should be used to unload assets.
/// update_fun takes a GameTime and a state, and should produce draw data and computation
/// data.
/// draw_fun takes a game time and draw data and should return nothing.
/// compute_fun takes a game time and computation data and should return a new state.
type ParallelUpdateDrawGameComponent<'State, 'DrawData, 'ComputationData>
    (game,
     initial_state : 'State,
     initialize_fun : unit -> unit,
     update_fun : GameTime -> 'State -> 'DrawData * 'ComputationData,
     compute_fun : GameTime -> 'ComputationData -> 'State,
     draw_fun : GameTime -> 'DrawData -> unit,
     dispose : unit -> unit) =

    inherit DrawableGameComponent(game)

    let mutable state = initial_state
    let mutable draw_data = Unchecked.defaultof<'DrawData>
    let mutable compute_data = Unchecked.defaultof<'ComputationData>
    let mutable gt_shared = GameTime()

    let mutable enabled = true
    let mutable update_order = 0

    let signal_start = new AutoResetEvent(false)
    let mutable kill_requested = false
    let signal_done = new AutoResetEvent(false)

    let do_compute() =
#if XBOX360
        // Set affinity
        // 0 and 2 are reserved, I assume the "main" thread is 1.
        Thread.CurrentThread.SetProcessorAffinity(3)
#endif
        while not kill_requested do
            signal_start.WaitOne() |> ignore
            state <- compute_fun gt_shared compute_data
            signal_done.Set() |> ignore

    let compute_thread = new Thread(new ThreadStart(do_compute))

    // Must be called from the main thread.
    let post_compute_then_draw gt =
        if not kill_requested then
            let state = state
            gt_shared <- gt
            signal_start.Set() |> ignore
            draw_fun gt draw_data
            signal_done.WaitOne() |> ignore

    let mutable frameCounter = 0
    let mutable timeCounter = 0.0
    let mutable fps = 0.0
    let fpsUpdatePeriod = 0.3

    do
        compute_thread.IsBackground <- true
        compute_thread.Start()

    override this.Initialize() =
        base.Initialize()
        initialize_fun()

    override this.Update(gt) =
        if base.Enabled then
            base.Update(gt)
            let draw, compute = update_fun gt state
            draw_data <- draw
            compute_data <- compute

    override this.Draw(gt) =
        if base.Visible then
            base.Draw(gt)
            post_compute_then_draw gt
        else
            state <- compute_fun gt compute_data
        timeCounter <- timeCounter + gt.ElapsedGameTime.TotalSeconds
        frameCounter <- frameCounter + 1
        if timeCounter > fpsUpdatePeriod then
            fps <- float frameCounter / timeCounter
            timeCounter <- timeCounter - fpsUpdatePeriod
            frameCounter <- 0

    
    interface System.IDisposable with
        member this.Dispose() =
            base.Dispose()
            dispose()
            signal_start.Dispose()
            signal_done.Dispose()

    interface IFramePerSecondCounter with
        member this.FramesPerSecond = fps

    member this.FramesPerSecond = fps

    member this.RequestKill() =
        kill_requested <- false
        signal_start.Set() |> ignore

    member this.WaitUntilDead() =
        compute_thread.Join()

    member this.IsDead = not(compute_thread.IsAlive)

To be noted is that this component isn't meant to be extended the usual way which consists in inheriting and overriding. I'm experimenting with staying away from traditional OOP. I'm not sure it's the nicest way to do things, but building a wrapper from which to inherit shouldn't be hard. The OOP way will definitely be more appealing when using this component from C#, so I'll probably have to take this step anyway.

The constructor of the class takes an initial state and an initializing function which shouldn't be mixed. The initializing function is meant for loading assets. The dispose function should undo the effects of the initializing function and should dispose of any disposable asset.

The initial state represents the state of the world when the game starts. This is typically built from a level description when entering a new level, or by loading a previously saved session.

When the game is running, the state is passed to the update function, which isn't so well named, in retrospect. Its role is to prepare data for the compute and draw functions, which are run in parallel. In most cases I expect that ComputationData and State are the same type.

As is common in parallel update/draw scenarios, the draw function renders the state produced by the compute function in the previous frame. This is necessary to avoid race conditions between the compute and draw functions.

I am not yet sure whether I'm happy with my implementation of IDisposable, and this may change if turns out to be impractical or wrong. I've been using this component in a new game I'm working on, and I have been positively surprised. I hope you will find it useful!