Chapter 8. Mastering F#: Common Techniques

F# is a powerful language with relatively simple constructs. Learning the constructs of the language is easy, but learning how to use the constructs well takes a little more time. This chapter presents some of the common F# coding techniques you need as you work across multiple programming domains. These techniques are either applications of the constructs you've encountered so far or relate to the foundational libraries that ship with F# and .NET.

Equality, Hashing, and Comparison

In Chapter 5, you saw a number of predefined generic operations, including generic comparison, equality, and hashing, accessed via functions such as those shown here:

val compare : 'T -> 'T -> int when 'T : comparison
val (=)   : 'T -> 'T -> bool when 'T : equality
val (<)   : 'T -> 'T -> bool when 'T : comparison
val (<=)  : 'T -> 'T -> bool when 'T : comparison
val (>)   : 'T -> 'T -> bool when 'T : comparison
val (>=)  : 'T -> 'T -> bool when 'T : comparison
val min : 'T -> 'T -> 'T when 'T : comparison
val max : 'T -> 'T -> 'T when 'T : comparison
val hash  : 'T -> int when 'T : equality

First, note that these are generic operations—they can be used on objects of many different types. This can be seen by the use of 'T in the signatures of these operations. The operations take one or two parameters of the same type. For example, you can apply the = operator to two Form objects, or two System.DateTime objects, or two System.Type objects, and something reasonable happens. Some other important derived generic types such as the immutable (persistent) Set<_> and Map<_,_> types in the F# library also use generic comparison on their key type:

type Set<'T when 'T : comparison> = ...
type Map<'Key,'Value when 'Key : comparison> = ...

These operations and types are all constrained, in this case by the equality and/or comparison constraints. The purpose of constraints on type parameters is to make sure the operations are only used on a particular set of types. For example, consider equality and ordered comparison on a System.Windows.Forms.Form object. Equality is permitted, because the default for nearly all .NET object types is reference equality:

let form1 = new System.Windows.Forms.Form()
let form2 = new System.Windows.Forms.Form()
form1 = form1    // true
form1 = form2    // false

However, ordered comparison isn't permitted:

let form1 = new System.Windows.Forms.Form()
let form2 = new System.Windows.Forms.Form()
form1 <= form2
    // Error: The type 'Form' does not support the 'comparison' constraint.
    // For example, it does not support the 'System.IComparable' interface

That's good! There is no natural ordering for form objects, or at least no ordering is provided by the .NET libraries.

Equality and comparison can work over the structure of types. For example, you can use the equality operators on a tuple only if the constituent parts of the tuple also support equality. This means using equality on a tuple of forms is permitted:

let form1 = new System.Windows.Forms.Form()
let form2 = new System.Windows.Forms.Form()
(form1, form2) = (form1, form2) // true
(form1, form2) = (form2, form1) // false

But using ordered comparison of a tuple isn't:

(form1, "Data for Form1") <= (form2, " Data for Form2")
    // Error: The type 'System.Windows.Forms.Form' does not
    // support the 'comparison' constraint.

Again, that's good—this ordering would be a bug in your code. Now, let's take a closer look at when equality and comparison constraints are satisfied in F#.

  • The equality constraint is satisfied if the type definition doesn't have the NoEquality attribute, and any dependencies also satisfy the equality constraint.

  • The comparison constraint is satisfied if the type definition doesn't have the NoComparison attribute, and the type definition implements System.IComparable, and any dependencies also satisfy the comparison constraint.

An equality constraint is relatively weak, because nearly all CLI types satisfy it. A comparison constraint is a stronger constraint, because it usually implies that a type must implement System.IComparable.

Asserting Equality, Hashing, and Comparison Using Attributes

The following attributes control the comparison and equality semantics of type definitions:

  • StructuralEquality and StructuralComparison: Indicate that a structural type must support equality and comparison

  • NoComparison and NoEquality: Indicate that a type doesn't support equality or comparison

  • CustomEquality and CustomComparison: Indicate that a structural type supports custom equality and comparison

Let's look at examples of these. Sometimes you may want to assert that a structural type must support structural equality, and you want an error at the definition of the type if it doesn't. You do this by adding the StructuralEquality or StructuralComparison attribute to the type:

[<StructuralEquality;StructuralComparison>]
type MiniIntegerContainer = MiniIntegerContainer of int

This adds extra checking. In the following example, the code gives an error at compile time—the type can't logically support automatic structural comparison because one of the element types doesn't support ordered comparison:

[<StructuralEquality;StructuralComparison>]
type MyData = MyData of int * string * string * System.Windows.Forms.Form


   error FS1177: The struct, record or union type 'MyData' has the
   'StructuralComparison' attribute but the component type
   'System.Windows.Forms.Form' does not satisfy the 'comparison' constraint

Fully Customizing Equality, Hashing, and Comparison on a Type

Many types in the .NET libraries come with custom equality, hashing and comparison implementations. For example, System.DateTime has custom implementations of these.

F# also allows you to define custom equality, hashing, and comparison for new type definitions. For example, values of a type may carry a unique integer tag that can be used for this purpose. In such cases, we recommend that you take full control of your destiny and define custom comparison and equality operations on your type. For example, Listing 8-1 shows how to customize equality, hashing and comparison based on a unique stamp integer value. The type definition includes an implementation of System.IComparable and overrides of Object.Equals and Object.GetHashCode.

Example 8.1. Customizing Equality, Hashing, and Comparison for a Record Type Definition

/// A type abbreviation indicating we're using integers for unique stamps
/// on objects
type stamp = int

/// A structural type containing a function that can't be compared for equality
[<CustomEquality; CustomComparison>]
type MyThing =
    { Stamp: stamp;
      Behaviour: (int -> int) }

    override x.Equals(yobj) =
        match yobj with
        | :? MyThing as y -> (x.Stamp = y.Stamp)
        | _ -> false
override x.GetHashCode() = hash x.Stamp
    interface System.IComparable with
      member x.CompareTo yobj =
          match yobj with
          | :? MyThing as y -> compare x.Stamp y.Stamp
          | _ -> invalidArg "yobj" "cannot compare values of different types"

The System.IComparable interface is defined in the .NET libraries:

namespace System

    type IComparable =
          abstract CompareTo : obj -> int

Recursive calls to compare subexpressions are processed using the following functions:

val hash : 'T -> int when 'T : equality
val (=) : 'T -> 'T -> bool when 'T : equality
val compare : 'T -> 'T -> int when 'T : comparison

Listing 8-2 shows the same for a union type, this time using some helper functions.

Example 8.2. Customizing Generic Hashing and Comparison on a Union Type

let inline equalsOn f x (yobj:obj) =
 match yobj with
 | :? 'T as y -> (f x = f y)
 | _ -> false

let inline hashOn f x = hash (f x)

let inline compareOn f x (yobj: obj) =
match yobj with
| :? 'T as y -> compare (f x) (f y)
| _ -> invalidArg "yobj" "cannot compare values of different types"

type stamp = int

[<CustomEquality; CustomComparison>]
type MyUnionType =
    | MyUnionType of stamp * (int -> int)

    static member Stamp (MyUnionType (s,_)) = s

    override x.Equals y = equalsOn MyUnionType.Stamp x y
    override x.GetHashCode() = hashOn MyUnionType.Stamp x
    interface System.IComparable with
      member x.CompareTo y = compareOn MyUnionType.Stamp x y

Listing 8-2 also shows how to implement the System.Object method GetHashCode. This follows the same pattern as generic equality.

Finally, you can declare that a structural type should use reference equality:

[<ReferenceEquality>]
type MyFormWrapper = MyFormWrapper of System.Windows.Forms.Form * (int -> int)

There is no such thing as reference comparison (the object pointers used by .NET move around, so the ordering would change). You can implement that by using a unique tag and custom comparison.

Suppressing Equality, Hashing, and Comparison on a Type

You can suppress equality on an F# defined type by using the NoEquality attribute on the definition of the type. This means the type isn't considered to satisfy the equality constraint. Likewise, you can suppress comparison on an F# defined type by using the NoComparison attribute on the definition of the type:

[<NoEquality; NoComparison>]
type MyProjections =
    | MyProjections of (int * string) * (string -> int)

Adding these attributes to your library types makes client code safer, because it's less likely to inadvertently rely on equality and comparison over types where these operations make no sense.

Customizing Generic Collection Types

Programmers love defining new generic collection types. This is done less often in .NET and F# programming than in other languages, because the F# and .NET built-in collections are so good, but it's still important.

Equality and comparison play a role here. For example, it's common to have collections where some of the values can be indexed using hashing, compared for equality when searching, or compared using an ordering. For example, seeing a constraint on this signature on a library type would come as no surprise:

type Graph<'Node when 'Node : equality>() = ...

The presence of the constraint is somewhat reassuring, because the requirement on node types is made clearer. Sometimes it's also desirable to be able to compare entire containers: for example, to compare one set with another, one map with another, or one graph with another. Consider the simplest generic collection type of all, which holds only one element. You can define it easily in F#:

type MiniContainer<'T> = MiniContainer of 'T

In this case, this is a structural type definition, and F# infers that there is an equality and comparison dependency on 'T. All done! You can use MiniContainer<_> with values of any type, and you can only do equality and comparison on MiniContainer values if the element type also supports equality and comparison. Perfect.

However, if MiniContainer is a class type or has customized comparison and equality logic, then you need to be more explicit about dependencies. You can declare dependencies by using the EqualityConditionalOn and ComparisonConditionalOn attributes on the type parameter. You should also use the operators Unchecked.equals, Unchecked.hash, and Unchecked.compare to process elements recursively. With these attributes, MiniContainer<A> satisfies the equality and comparison constraints if A satisfies these constraints. Here's a full example:

type MiniContainer<[<EqualityConditionalOn; ComparisonConditionalOn >]'T>(x : 'T) =
    member x.Value = x
    override x.Equals(yobj) =
        match yobj with
        | :? MiniContainer<'T> as y -> Unchecked.equals x.Value y.Value
        | _ -> false

    override x.GetHashCode() = Unchecked.hash x.Value

    interface System.IComparable with
      member x.CompareTo yobj =
          match yobj with
          | :? MiniContainer<'T> as y -> Unchecked.compare x.Value y.Value
          | _ -> invalidArg "yobj" "cannot compare values of different types"

Note

Be careful about using generic equality, hashing, and comparison on mutable data. Changing the value of a field may change the value of the hash or the results of the operation. It's normally better to use the operations on immutable data or data with custom implementations.

Efficient Precomputation and Caching

All experienced programmers are familiar with the concept of precomputation, where computations are performed as soon as some of the inputs to a function are known. The following sections cover a number of manifestations of precomputation in F# programming and the related topics of memoization and caching.

Precomputation and Partial Application

Let's say you're given a large input list of words and you want to compute a function that checks whether a word is in this list. You can do this as follows:

let isWord (words: string list) =
    let wordTable = Set.ofList words
    fun w -> wordTable.Contains(w)

Here, isWord has the following type:

val isWord : string list -> (string -> bool)

The efficient use of this function depends crucially on the fact that useful intermediary results are computed after only one argument is applied. For example:

> let isCapital = isWord ["London";"Paris";"Warsaw";"Tokyo"];;
val isCapital : (string -> bool)

> isCapital "Paris";;
val it : bool = true

> isCapital "Manchester";;
val it : bool = false

Here, the internal table wordTable is computed as soon as isCapital is applied to one argument. It would be a mistake to write isCapital as follows:

let isCapitalSlow inp = isWord ["London";"Paris";"Warsaw";"Tokyo"] inp

This function computes the same results as isCapital. However, it does so inefficiently, because isWord is applied to both its first argument and its second argument every time you use the function isCapitalSlow. This means the internal table is rebuilt every time the function isCapitalSlow is applied, somewhat defeating the point of having an internal table in the first place. In a similar vein, the definition of isCapital shown previously is more efficient than either isCapitalSlow2 or isCapitalSlow3 in the following:

let isWordSlow2 (words: string list) (word:string) =
    List.exists (fun word2 -> word = word2) words

let isCapitalSlow2 inp = isWordSlow2 ["London";"Paris";"Warsaw";"Tokyo"] inp

let isWordSlow3 (words: string list) (w:string) =
    let wordTable = Set.Create(words)
    wordTable.Contains(w)

let isCapitalSlow3 inp = isWordSlow3 ["London";"Paris";"Warsaw";"Tokyo"] inp

The first uses an inappropriate data structure for the lookup (an F# list, which has O(n) lookup time), and the second attempts to build a better intermediate data structure (an F# set, which has O(log n) lookup time) but does so on every invocation.

There are often trade-offs between different intermediate data structures or whether to use intermediate data structures at all. For example, in the previous example, you could just as well use a HashSet as the internal data structure. This approach in general gives better lookup times (constant time), but it requires slightly more care to use because a HashSet is a mutable data structure. In this case, you don't mutate the data structure after you create it, and you don't reveal it to the outside world, so it's entirely safe:

#r "System.Core.dll"
let isWord (words: string list) =
    let wordTable = System.Collections.Generic.HashSet<_>(words)
    fun word -> wordTable.Contains(word)

Precomputation and Objects

The examples of precomputation given previously are variations on the theme of computing functions, introduced in Chapter 3. The functions computed capture the precomputed intermediate data structures. However, it's clear that precomputing via partial applications and functions can be subtle, because it matters when you apply the first argument of a function (triggering the construction of intermediate data structures) and when you apply the subsequent arguments (triggering the real computation that uses the intermediate data structures).

Luckily, functions don't just have to compute functions; they can also return more sophisticated values such as objects. This can help make it clear when precomputation is being performed. It also allows you to build richer services based on precomputed results. For example, Listing 8-3 shows how to use precomputation as part of building a name-lookup service. The returned object includes both a Contains method and a ClosestPrefixMatch method.

Example 8.3. Precomputing a Word Table Before Creating an Object

open System

type NameLookupService =
    abstract Contains : string -> bool

let buildSimpleNameLookup (words: string list) =
    let wordTable = Set.ofList words
    let score (w1:string) (w2:string) =
        let lim = min w1.Length w2.Length
        let rec loop i acc =
            if i >= lim then acc
            else loop (i+1) (int w1.[i] - int w2.[i] + acc)
        loop 0 0

    { new NameLookupService with
        member t.Contains(w) = wordTable.Contains(w) }

The internal data structure used in Listing 8-3 is the same as before: an F# set of type Microsoft.FSharp.Collections.Set<string>. The service can now be instantiated and used as follows:

> let capitalLookup = buildSimpleNameLookup ["London";"Paris";"Warsaw";"Tokyo"];;
val capitalLookup : NameLookupService

> capitalLookup.Contains "Paris";;
val it : bool = true

In passing, note the following about this implementation:

  • The table is built based on the F# default ordinal comparison for strings. This isn't always an appropriate choice when you're using natural-language text. You can specify the exact comparison function to use when building sets based on string values by creating a custom key type with a custom comparison function.

  • You can extend the returned service to support a richer set of queries of the underlying information by adding further methods to the object returned.

Precomputation of the kind used previously is an essential technique for implementing many services and abstractions, from simple functions to sophisticated computation engines. You see further examples of these techniques in Chapter 9.

Memoizing Computations

Precomputation is one important way to amortize the costs of computation in F#. Another is called memoization. A memoizing function is one that avoids recomputing its results by keeping an internal table, often called a lookaside table. For example, consider the well-known Fibonacci function, whose naive, unmemoized version is as follows:

let rec fib n = if n <= 2 then 1 else fib (n-1) + fib (n-2)

Not surprisingly, a version keeping a lookaside table is much faster:

#nowarn "40" // do not warn on recursive computed objects and functions
let fibFast =
    let t = new System.Collections.Generic.Dictionary<int,int>()
    let rec fibCached n =
        if t.ContainsKey(n) then t.[n]
        else if n <= 2 then 1
        else let res = fibCached(n-1) + fibCached(n-2)
             t.Add(n,res)
             res
    fun n -> fibCached n

On one of our laptops, with n = 30, the first runs in 3.65 seconds, and the second runs in 0.015 seconds.

Listing 8-4 shows how to write a generic function that encapsulates the memoization technique.

Example 8.4. A Generic Memoization Function

open System.Collections.Generic
let memoize (f: 'T -> 'U) =
    let t = new Dictionary<'T,'U>(HashIdentity.Structural)
    fun n ->
        if t.ContainsKey(n) then t.[n]
        else let res = f n
             t.Add(n,res)
             res

let rec fibFast =
    memoize (fun n -> if n <= 2 then 1 else fibFast (n-1) + fibFast (n-2))

Here, the functions have the following types:

val memoize : ('T -> 'U) -> ('T -> 'U) when 'T : equality
val fibFast : (int -> int)

In the definition of fibFast, you use let rec because fibFast is self-referential—that is, used as part of its own definition. You can think of fibFast as a computed, recursive function. Such a function generates an informational wwarning when used in F# code, because it's important to understand when this feature of F# is being used; you then suppress the warning with #nowarn "40". As with the examples of computed functions from the previous section, it's important not to include the extra argument in the application of memoize, because it would lead to a fresh memoization table being allocated each time the function fibNotFast was called:

let rec fibNotFast n =
    memoize (fun n -> if n <= 2 then 1 else fibNotFast (n-1) + fibNotFast (n-2)) n

Due to this subtlety, it's often a good idea to define your memoization strategies to generate objects other than functions (note that you can think of functions as very simple kinds of objects). For example, Listing 8-5 shows how to define a new variation on memoize that returns a Table object that supports both a lookup and a Discard method.

Example 8.5. A Generic Memoization Service

open System.Collections.Generic
type Table<'T,'U> =
    abstract Item : 'T -> 'U with get
    abstract Discard : unit -> unit

let memoizeAndPermitDiscard f =
    let lookasideTable = new Dictionary<_,_>(HashIdentity.Structural)
    { new Table<'T,'U> with
          member t.Item
             with get(n) =
                 if lookasideTable.ContainsKey(n)
                 then lookasideTable.[n]
                 else let res = f n
                      lookasideTable.Add(n,res)
                      res
          member t.Discard() =
              lookasideTable.Clear() }


#nowarn "40" // do not warn on recursive computed objects and functions

let rec fibFast =
    memoizeAndPermitDiscard
        (fun n ->
            printfn "computing fibFast %d" n
            if n <= 2 then 1 else fibFast.[n-1] + fibFast.[n-2])

In Listing 8-5, lookup uses the a.[b] associative Item lookup property syntax, and the Discard method discards any internal partial results. The functions have the following types:

val memoizeAndPermitDiscard : ('T -> 'U) -> Table<'T, 'U> when 'T : equality
val fibFast : Table<int,int>

Here's an example showing how fibFast caches results but recomputes them after a Discard:

> fibFast.[3];;
computing fibFast 3
computing fibFast 2
computing fibFast 1
val it : int = 2

> fibFast.[5];;
computing fibFast 5
computing fibFast 4
val it : int = 5

> fibFast.Discard();;
val it : unit = ()

> fibFast.[5];;
computing fibFast 5
computing fibFast 4
computing fibFast 3
computing fibFast 2
computing fibFast 1
val it : int = 5

Note

Memoization relies on the memoized function being stable and idempotent. In other words, it always returns the same results, and no additional interesting side effects are caused by further invocations of the function. In addition, memoization strategies rely on mutable internal tables. The implementation of memoize shown in this chapter isn't thread safe, because it doesn't lock this table during reading or writing. This is fine if the computed function is used only from at most one thread at a time; but in a multithreaded application, you should use memoization strategies that use internal tables protected by locks such as a .NET ReaderWriterLock. Chapter 13 discusses thread synchronization and mutable state further.

Lazy Values

Memoization is a form of caching. Another important variation on caching is a simple lazy value. A lazy value is a delayed computation of type Microsoft.FSharp.Control.Lazy<'T> for some type 'T. Lazy values are usually formed by using the special keyword lazy (you can also make them explicitly using the functions in the Microsoft.FSharp.Core.Lazy module). For example:

> let sixty = lazy (30+30);;
val sixty : Lazy<int>

> sixty.Force();;
val it : int = 60

Lazy values of this kind are implemented as thunks holding either a function value that computes the result or the actual computed result. The lazy value is computed only once, and thus its effects are executed only once. For example, in the following code fragment, "Hello world" is printed only once:

> let sixtyWithSideEffect = lazy (printfn "Hello world"; 30+30);;
val sixtyWithSideEffect: Lazy<int>

> sixtyWithSideEffect.Force();;
Hello world
val it : int = 60

> sixtyWithSideEffect.Force();;
val it : int = 60

Lazy values are implemented by a simple data structure containing a mutable reference cell. You can find the definition of this data structure in the F# library source code.

Other Variations on Caching and Memoization

You can apply many different caching and memoization techniques in advanced programming, and this chapter can't cover them all. Here are some common variations:

  • Using an internal data structure that records only the last invocation of a function and basing the lookup on a very cheap test on the input.

  • Using an internal data structure that contains both a fixed-size queue of input keys and a dictionary of results. Entries are added to both the table and the queue as they're computed. When the queue is full, the input keys for the oldest computed results are dequeued, and the computed results are discarded from the dictionary.

Cleaning Up Resources

All programming involves the use of real resources on the host machine(s) and operating system. For example:

  • Stack: Implicitly allocated and deallocated as functions are called

  • Heap allocated memory: Used by all reference-typed objects

  • File handles: Such as operating system file handles represented by System.IO.FileStream objects and its subtypes

  • Network connections: Such as operating system I/O completion ports represented by System.Net.WebResponse and its subtypes

  • Threads: Such as operating system threads represented by System.Threading.Thread objects and also worker threads in the .NET thread pool

  • Graphics objects: Such as drawing objects represented by various constructs under the System.Drawing namespace

  • Concurrency objects: Such as operating system synchronization objects represented by System.Threading.WaitHandle objects and its subtypes

All resources are necessarily finite. In .NET programming, some resources such as memory are fully managed, in the sense that you almost never need to consider when to clean up memory. This is done automatically through a process called garbage collection. Chapter 17 looks at garbage collection in a little more detail. Other resources must be reclaimed and/or recycled.

When prototyping, you can generally assume that resources are unbounded, although it's good practice when you're using a resource to be aware of how much of the resource you're using and roughly what your budget for the resource is. For example:

  • On a modern 32-bit desktop machine, 10,000 tuple values occupy only a small fragment of a machine's memory, roughly 160KB. However, 10,000 open file handles is an extreme number and will stress the operating system. 10,000 simultaneous web requests may stress your network administrator!

  • In some cases, even memory should be explicitly and carefully reclaimed. For example, on a modern 64-bit machine, the largest single array you can allocate in a .NET 2.0 program is 2GB. If your machine has, say, 4GB of real memory, you may be able to have only a handful of these objects and should strongly consider moving to a regime where you explicitly recycle these objects and think carefully before allocating them.

Cleaning Up with use

With the exception of stack and memory, all objects that own resources should be subtypes of the .NET type System.IDisposable. This is the primary way you can recognize primitive resources and objects that wrap resources. The System.IDisposable interface has a single method; in F# syntax, it can be defined as follows:

namespace System
    type IDisposable =
        abstract Dispose: unit -> unit

One of the simplest approaches to managing IDisposable objects is to give each resource a lifetime: that is, some well-defined portion of the program execution for which the object is active. This is even easier when the lifetime of a resource is lexically scoped, such as when a resource is allocated on entry to a function and deallocated on exit. In this case, the resource can be tied to the scope of a particular variable, and you can protect and dispose of a value that implements IDisposable by using a use binding instead of a let binding. For example, in the following code, three values implement IDisposable, all of which are bound using use:

/// Fetch a web page
let http (url: string) =
    let req = System.Net.WebRequest.Create url
    use resp = req.GetResponse()
    use stream = resp.GetResponseStream()
    use reader = new System.IO.StreamReader(stream)
    let html = reader.ReadToEnd()
    html

In all three cases, the objects (a WebResponse, a Stream, and a StreamReader) are automatically closed and disposed at the end of an execution of the function. To see what's going on, notice that a use binding is syntactic sugar. For example, the following

usevar = expr in body

is shorthand for this:

let var = expr
    try body
    finally
        match var with
        | null -> ()
        |  _ -> var.Dispose()

A number of important types implement IDisposable; Table 8-1 shows some of them. You can use tables such as this to chart the portions of the .NET Framework that reveal operating system functionality to .NET applications.

Table 8.1. A Selection of the Types That Implement IDisposable

Namespace

Some Types Implementing IDisposable

System.IO

BinaryReader,BinaryWriter,FileSystemWatcher,IsolatedFileStorage,Stream,TextReader,TextWriter,...

System.Drawing

Brush, BufferedGraphics,Font,FontFamily,Graphics,Icon,Image,Pen,Region,TextureBrush,...

System.Drawing.Text

FontCollection,...

System.Drawing.Drawing2D

CustomLineCap,GraphicsPath,GraphicsPathIterator,Matrix,...

System.Drawing.Imaging

EncoderParameter,ImageAttributes,...

System.Net

WebResponse,...

System.Net.Sockets

Socket, TcpClient,...

System.Data.SqlClient

SqlBulkCopy,SqlCommand,SqlConnection,SqlTransaction,...

System.Threading

Timer, WaitHandle,AutoResetEvent,ManualResetEvent,Mutex,Semaphore,...

System.Web.UI

Control, HttpApplication, ...

System.Web.UI.WebControls

Button, CheckBox,DataGrid,...

System.Windows.Forms

Button, CheckBox,Cursor,Control,DataGrid,Form,...

Microsoft.Win32

RegistryKey,...

Tip

A tool such as Visual Studio can help you determine when a type has implemented IDisposable. When you rest your mouse pointer over a value, you normally see this noted on the information displayed for a value.

Managing Resources with More Complex Lifetimes

Sometimes, the lifetime of a resource isn't simple in the sense that it doesn't follow a stack discipline. In these cases, you should almost always adopt one of two techniques:

  • Design objects that can own one or more resources and that are responsible for cleaning them up. Make sure these objects implement System.IDisposable.

  • Use control constructs that help you capture the kind of computation you're performing. For example, when generating sequences of data (such as from a database connection), you should strongly consider using sequence expressions, discussed in Chapter 3. These may have internal use bindings, and the resources are disposed when each sequence iteration finishes. Likewise, when using asynchronous I/O, it may be helpful to write your computation as an asynchronous workflow. Chapter 13 and the following sections provide examples.

You should consider implementing the IDisposable interface on objects and types in the following situations:

  • When you build an object that uses one or more IDisposable objects internally.

  • When you're writing a wrapper for an operating system resource or some resource allocated and managed in a native (C or C++) DLL. In this case, you should also implement a finalizer by overriding the Object.Finalize method.

  • When you implement the System.Collections.Generic.IEnumerable<'T> (that is, sequence) interface on a collection. The IEnumerable interface isn't IDisposable, but it must generate System.Collection.Generic.IEnumerator<'T> values, and this interface inherits from IDisposable. For nearly all collection types, the disposal action returns without doing anything.

The following sections give some examples of these.

Cleaning Up Internal Objects

Listing 8-6 shows an example that implements an object that reads lines from a pair of text files, choosing the file at random. You must implement the type IDisposable because the object owns two internal System.IO.StreamReader objects, which are IDisposable. Note that you explicitly check to see whether the object has already been disposed.

Example 8.6. Implementing IDisposable to Clean Up Internal Objects

open System
open System.IO

type LineChooser(fileName1, fileName2) =
    let file1 = File.OpenText(fileName1)
    let file2 = File.OpenText(fileName2)
    let rnd = new System.Random()

    let mutable disposed = false

    let cleanup() =
        if not disposed then
            disposed <- true;
            file1.Dispose();
            file2.Dispose();

    interface System.IDisposable with
        member x.Dispose() = cleanup()

    member obj.CloseAll() = cleanup()

    member obj.GetLine() =
        if not file1.EndOfStream &&
           (file2.EndOfStream  || rnd.Next() % 2 = 0) then file1.ReadLine()
        elif not file2.EndOfStream then file2.ReadLine()
        else raise (new EndOfStreamException())

You can now instantiate, use, and dispose of this object as follows:

> open System.IO;;

> File.WriteAllLines("test1.txt", [| "Daisy, Daisy"; "Give me your hand oh do" |]);;
val it : unit = ()

> File.WriteAllLines("test2.txt", [| "I'm a little teapot"; "Short and stout" |]);;
val it : unit = ()

> let chooser = new LineChooser ("test1.txt", "test2.txt");;
val chooser : LineChooser

> chooser.GetLine();;
val it : string = "Daisy, Daisy"

> chooser.GetLine();;
val it : string = "I'm a little teapot"

> (chooser :> IDisposable).Dispose();;
val it : unit = ()

> chooser.GetLine();;
System.ObjectDisposedException: Cannot read from a closed TextReader.

Disposal should leave an object in an unusable state, as shown in the last line of the previous example. It's also common for objects to implement a member with a more intuitive name that does precisely the same thing as its implementation of IDisposable.Dispose, which is CloseAll in Listing 8-6.

Cleaning Up Unmanaged Objects

If you're writing a component that explicitly wraps some kind of unmanaged resource, then implementing IDisposable is a little trickier. Listing 8-7 shows the pattern that is used for this cleanup. Here, you mimic an external resource via a data structure that generates fresh, reclaimable integer tickets. The idea is that customers are each given an integer ticket, but this is kept internal to the customer, and customers return their ticket to the pool when they leave (that is, are disposed).

Example 8.7. Reclaiming Unmanaged Tickets with IDisposable

open System

type TicketGenerator() =
    let mutable free = []
    let mutable max = 0
    member h.Alloc() =
        match free with
        | [] -> max <- max + 1; max
        | h::t -> free <- t; h
    member h.Dealloc(n:int) =
        printfn "returning ticket %d" n
        free <- n :: free
let ticketGenerator = new TicketGenerator()

type Customer() =
    let myTicket = ticketGenerator.Alloc()
    let mutable disposed = false
    let cleanup() =
         if not disposed then
             disposed <- true
             ticketGenerator.Dealloc(myTicket)
    member x.Ticket = myTicket
    interface IDisposable with
         member x.Dispose() = cleanup(); GC.SuppressFinalize(x)
    override x.Finalize() = cleanup()

Note that you override the Object.Finalize method. This makes sure cleanup occurs if the object isn't disposed but is still garbage-collected. If the object is explicitly disposed, you call GC.SuppressFinalize() to ensure that the object isn't later finalized. The finalizer shouldn't call the Dispose() of other managed objects, because they have their own finalizers if needed. The following example session generates some customers, and tickets used by some of the customers are automatically reclaimed as they exit their scopes:

> let bill = new Customer();;
val bill : Customer

> bill.Ticket;;
val it : int = 1

> begin
      use joe = new Customer()
      printfn "joe.Ticket = %d" joe.Ticket
  end;;
joe.Ticket = 2
returning ticket 2

> begin
      use jane = new Customer()
      printfn "jane.Ticket = %d" jane.Ticket
  end;;
jane.Ticket = 2
returning ticket 2
val it : unit = ()

In the example, Joe and Jane get the same ticket. Joe's ticket is returned at the end of the scope where the joe variable is declared because of the IDisposable cleanup implicit in the use binding.

Cleaning Up in Sequence Expressions

It's common to implement computations that access external resources such as databases but that return their results on demand. But this raises a difficulty: how do you manage the lifetime of the resources for the underlying operating system connections? One solution to this is captured by use bindings in sequence expressions:

  • When a use binding occurs in a sequence expression, the resource is initialized each time a client enumerates the sequence.

  • The connection is closed when the client disposes of the enumerator.

For example, consider the following function that creates a sequence expression that reads the first two lines of a file on demand:

open System.IO

let firstTwoLines(file) =
    seq { use s = File.OpenText(file)
          yield s.ReadLine()
          yield s.ReadLine() }

Let's now create a file and a sequence that reads the first two lines of the file on demand:

> File.WriteAllLines("test1.txt", [| "Es kommt ein Schiff";
                                     "A ship is coming" |]);;
val it : unit = ()

> let seq = firstTwoLines("test1.txt");;
val seq : seq<string>

At this point, the file hasn't yet been opened, and no lines have been read from the file. If you now iterate the sequence expression, the file is opened, the first two lines are read, and the results are consumed from the sequence and printed. Most important, the file has now also been closed, because the Seq.iter aggregate operator is careful to dispose of the underlying enumerator it uses for the sequence, which in turn disposes of the file handle generated by File.OpenText:

> seq |> Seq.iter (printfn "line = '%s'");;
line = 'Es kommt ein Schiff'
line = A ship is coming'

Chapter 9 covers sequence expressions and the more general mechanism of workflows in more detail.

Using using

In some older F# code, you may see the function using. For example:

using (new Customer()) (fun jane ->
    printfn "jane.Ticket = %d" jane.Ticket
)

The definition of using is as follows:

let using (ie : #System.IDisposable) f =
    try f(ie)
    finally ie.Dispose()

This is more explicit than writing use bindings but can be useful if you like to know what's going on under the hood.

Stack as a Resource: Tail Calls and Recursion

In the previous section, you saw a range of resources that are best managed explicitly, preferably by automatically cleaning up the construct at the end of its lifetime using constructs such as use x = expr and idioms such as System.IDisposable. You also saw that two resources are managed automatically, stack and heap-allocated memory, with the latter allocated on the garbage-collected heap.

Stack space is needed every time you call an F# function and is reclaimed when the function returns or when it performs a tail call, which is discussed in a moment. It's perhaps surprising that stack space is more limited than space in the garbage-collected heap. For example, on a 32-bit Windows machine, the default settings are such that each thread of a program can use up to 1MB of stack space. Because stack is allocated every time a function call is made, a very deep series of nested function calls causes a StackOverflowException to be raised. For example, on a 32-bit Windows machine, the following program causes a stack overflow when n reaches about 79000:

let rec deepRecursion n =
    if n = 1000000 then () else
    if n % 100 = 0 then
        printfn "--> deepRecursion, n = %d" n
    deepRecursion (n+1)
    printfn "<-- deepRecursion, n = %d" n

You can see this in F# Interactive:

> deepRecursion 0;;
--> deepRecursion, n = 0
...
--> deepRecursion, n = 79100
--> deepRecursion, n = 79200
--> deepRecursion, n = 79300
Process is terminated due to StackOverflowException
Session termination detected. Press Enter to restart.

Stack overflows are extreme exceptions, because it's often difficult to recover correctly from them. For this reason, it's important to ensure that the amount of stack used by your program doesn't grow in an unbounded fashion as your program proceeds, especially as you process large inputs. Furthermore, deep stacks can hurt in other ways; for example, the .NET garbage collector traverses the entire stack on every garbage collection. This can be expensive if your stacks are very deep.

Because recursive functions are common in F# functional programming, this may seem to be a major problem. However, there is one important case in which a function call recycles stack space eagerly: a tail call. A tail call is any call that is the last piece of work done by a function. For example, Listing 8-8 shows the same program with the last line deleted.

Example 8.8. A Simple Tail-Recursive Function

let rec tailCallRecursion n : unit =
    if n = 1000000 then () else
    if n % 100 = 0 then
        printfn "--> tailCallRecursion, n = %d" n
    tailCallRecursion (n+1)

The code now runs to completion without a problem:

> tailCallRecursion 0;;
...
--> tailCallRecursion, n = 999600
--> tailCallRecursion, n = 999700
--> tailCallRecursion, n = 999800
--> tailCallRecursion, n = 999900
val it : unit = ()

When a tail call is made, the .NET Common Language Runtime can drop the current stack frame before executing the target function, rather than waiting for the call to complete. Sometimes this optimization is performed by the F# compiler. If the n = 1000000 check were removed in the previous program, then the program would run indefinitely. (Note that n would cycle around to the negative numbers, because arithmetic is unchecked for overflow unless you open the module Microsoft.FSharp.Core.Operators.Checked.)

Functions such as tailCallRecursion are known as tail-recursive functions. When you write recursive functions, you should check either that they're tail recursive or that they won't be used with inputs that cause them to recurse to an excessive depth. The following sections, give some examples of techniques you can use to make your functions tail recursive.

Tail Recursion and List Processing

Tail recursion is particularly important when you're processing F# lists, because lists can be long and recursion is the natural way to implement many list-processing functions. For example, here is a function to find the last element of a list (this must traverse the entire list, because F# lists are pointers to the head of the list):

let rec last l =
    match l with
    | [] -> invalidArg "l" "the input list should not be empty"
    | [h] -> h
    | h::t -> last t

This function is tail recursive because no work happens after the recursive call last t. However, many list functions are written most naturally in non-tail-recursive ways. Although it can be a little annoying to write these functions using tail recursion, it's often better to use tail recursion than to leave the potential for stack overflow lying around your code. For example, the following function creates a list of length n where every entry in the list is the value x:

let rec replicateNotTailRecursiveA n x =
    if n <= 0 then []
    else x :: replicateNotTailRecursiveA (n-1) x

The problem with this function is that work is done after the recursive call. This becomes obvious when you write the function in the following fashion:

let rec replicateNotTailRecursiveB n x =
    if n <= 0 then []
    else
        let recursiveResult = replicateNotTailRecursiveB (n-1) x
        x :: recursiveResult

Clearly, a value is being constructed by the expression x :: recursiveResult after the recursive call replicateNotTailRecursiveB (n-1) x. This means the function isn't tail recursive. The solution is to write the function using an accumulating parameter. This is often done by using an auxiliary function that accepts the accumulating parameter:

let rec replicateAux n x acc =
    if n <= 0 then acc
    else replicateAux (n-1) x (x::acc)

let replicate n x = replicateAux n x []

Here, the recursive call to replicateAux is tail recursive. Sometimes the auxiliary functions are written as inner recursive functions:

let replicate n x =
    let rec loop i acc =
        if i >= n then acc
        else loop (i+1) (x::acc)
    loop 0 []

The F# compiler optimizes inner recursive functions such as these to produce an efficient pair of functions that pass extra arguments as necessary.

When you're processing lists, accumulating parameters often accumulate a list in reverse order. This means a call to List.rev may be required at the end of the recursion. For example, consider the following implementation of List.map, which isn't tail recursive:

let rec mapNotTailRecursive f inputList =
    match inputList with
    | [] -> []
    | h::t -> (f h) :: mapNotTailRecursive f t

Here is an implementation that neglects to reverse the accumulating parameter:

let rec mapIncorrectAcc f inputList acc =
    match inputList with
    | [] -> acc            // whoops! Forgot to reverse the accumulator here!
    | h::t -> mapIncorrectAcc f t (f h :: acc)

let mapIncorrect f inputList = mapIncorrectAcc f inputList []
> mapIncorrect (fun x -> x * x) [1;2;3;4];;
val it : int list = [ 16; 9; 4; 1]

Here is a correct implementation:

let rec mapAcc f inputList acc =
    match inputList with
    | [] -> List.rev acc
    | h::t -> mapAcc f t (f h :: acc)

let map f inputList = mapAcc f inputList []
> map (fun x -> x * x) [1;2;3;4];;
val it : int list = [ 1; 4; 9; 16]

Tail Recursion and Object-Oriented Programming

You often need to implement object members with a tail-recursive implementation. For example, consider the following list-like data structure:

type Chain =
    | ChainNode of int * string * Chain
    | ChainEnd of string

    member chain.LengthNotTailRecursive =
        match chain with
        | ChainNode(_,_,subChain) -> 1 + subChain.LengthNotTailRecursive
        | ChainEnd _ -> 0

The implementation of LengthNotTailRecursive is not tail recursive, because the addition 1 + applies to the result of the recursive property invocation. One obvious tail-recursive implementation uses a local recursive function with an accumulating parameter, as shown in Listing 8-9.

Example 8.9. Making an Object Member Tail Recursive

type Chain =
    | ChainNode of int * string * Chain
    | ChainEnd of string

    // The implementation of this property is tail recursive.
    member chain.Length =
let rec loop c acc =
            match c with
            | ChainNode(_,_,subChain) -> loop subChain (acc+1)
            | ChainEnd _ -> acc
        loop chain 0

Note

The list-processing functions in the F# library module Microsoft.FSharp.Collections.List are tail recursive, except where noted in the documentation. Some of them have implementations that are specially optimized to take advantage of the implementation of the list data structure.

Tail Recursion and Processing Unbalanced Trees

This section considers tail-recursion problems that are much less common in practice but for which it's important to know the techniques to apply if required. The techniques also illustrate some important aspects of functional programming, in particular an advanced technique called continuation passing.

Tree-structured data is generally more difficult to process in a tail-recursive way than list-structured data. For example, consider the following tree structure:

type Tree =
    | Node of string * Tree * Tree
    | Tip of string

let rec sizeNotTailRecursive tree =
    match tree with
    | Tip _ -> 1
    | Node(_,treeLeft,treeRight) ->
        sizeNotTailRecursive treeLeft + sizeNotTailRecursive treeRight

The implementation of this function isn't tail recursive. Luckily, this is rarely a problem, especially if you can assume that the trees are balanced. A tree is balanced when the depth of each subtree is roughly the same. In that case, a tree of depth 1,000 will have about 21000 entries. Even for a balanced tree of this size, the recursive calls to compute the overall size of the tree won't recurse to a depth greater than 1,000—not deep enough to cause stack overflow except when the routine is being called by some other function already consuming inordinate amounts of stack. Many data structures based on trees are balanced by design; for example, the Set and Map data structures implemented in the F# library are based on balanced binary trees.

However, some trees can be unbalanced; for example, you can explicitly make a highly unbalanced tree:

let rec mkBigUnbalancedTree n tree =
    if n = 0 then tree
    else Node("node",Tip("tip"),mkBigUnbalancedTree (n-1) tree)

let tree1 = Tip("tip")
let tree2 = mkBigUnbalancedTree 10000 tree1
let tree3 = mkBigUnbalancedTree 10000 tree2
let tree4 = mkBigUnbalancedTree 10000 tree3
let tree5 = mkBigUnbalancedTree 10000 tree4
let tree6 = mkBigUnbalancedTree 10000 tree5

Calling tree6.Size now risks a stack overflow. You can solve this in part by trying to predict whether the tree will be unbalanced to the left or right and by using an accumulating parameter:

let rec sizeAcc acc tree =
    match tree with
    | Tip _ -> 1+acc
    | Node(_,treeLeft,treeRight) ->
        let acc = sizeAcc acc treeLeft
        sizeAcc acc treeRight

let size tree = sizeAcc 0 tree

This algorithm works for tree6, because it's biased toward accepting trees that are skewed to the right. The recursive call that processes the right branch is a tail call, which the call that processes the left branch isn't. This may be OK if you have prior knowledge of the shape of your trees. However, this algorithm still risks a stack overflow, and if necessary, you may have to change techniques. One way to do this is to use a much more general and important technique known as continuation passing.

Using Continuations to Avoid Stack Overflows

A continuation is a function that receives the result of an expression after it's been computed. Listing 8-10 shows an example implementation of the previous algorithm that handles trees of arbitrary size.

Example 8.10. Making a Function Tail Recursive via an Explicit Continuation

let rec sizeCont tree cont =
    match tree with
    | Tip _ -> cont 1
    | Node(_,treeLeft,treeRight) ->
        sizeCont treeLeft (fun leftSize ->
          sizeCont treeRight (fun rightSize ->
            cont (leftSize + rightSize)))

let size tree = sizeCont tree (fun x -> x)

What's going on here? Let's look at the type of sizeCont and size:

val sizeCont : Tree -> (int -> 'a) -> 'a
val size : Tree -> int

The type of sizeCont tree cont can be read as "compute the size of the tree and call cont with that size." If you look at the type of sizeCont, you can see that it will call the second parameter of type int -> 'T at some point—how else could the function produce the final result of type 'T? And when you look at the implementation of sizeCont, you can see that it does call cont on both branches of the match.

Now, if you look at recursive calls in sizeCont, you can see that they're both tail calls:

sizeCont treeLeft (fun leftSize ->
  sizeCont treeRight (fun rightSize ->
    cont (leftSize + rightSize)))

That is, the first call to sizeCont is a tail call with a new continuation, as is the second. The first continuation is called with the size of the left tree, and the second is called with the size of the right tree. Finally, you add the results and call the original continuation cont. Calling size on an unbalanced tree such as tree6 now succeeds:

> size tree6;;
val it : int = 50001

How did you turn a tree walk into a tail-recursive algorithm? The answer lies in the fact that continuations are function objects, which are allocated on the garbage-collected heap. Effectively, you've generated a work list represented by objects, rather than keeping a work list via a stack of function invocations.

As it happens, using a continuation for both the right and left trees is overkill, and you can use an accumulating parameter for one side. This leads to a more efficient implementation because each continuation function object is likely to involve one allocation (short-lived allocations such as continuation objects are very cheap but not as cheap as not allocating at all!). For example, Listing 8-11 shows a more efficient implementation.

Example 8.11. Combining an Accumulator with an Explicit Continuation

let rec sizeContAcc acc tree cont =
    match tree with
    | Tip _ -> cont (1+acc)
    | Node (_, treeLeft, treeRight) ->
        sizeContAcc acc treeLeft (fun accLeftSize ->
        sizeContAcc accLeftSize treeRight cont)

let size tree = sizeContAcc 0 tree (fun x -> x)

The behavior of this version of the algorithm is as follows:

  1. You start with an accumulator acc of 0.

  2. You traverse the left spine of the tree until a Tip is found, building up a continuation for each Node along the way.

  3. When a Tip is encountered, the continuation from the previous Node is called with accLeftSize increased by 1. The continuation makes a recursive call to sizeContAcc for its right tree, passing the continuation for the second-to-last node along the way.

  4. When all is done, all the left and right trees have been explored, and the final result is delivered to the (fun x -> x) continuation.

As you can see from this example, continuation passing is a powerful control construct, although it's used only occasionally in F# programming.

Another Example: Processing Syntax Trees

One real-world example where trees may become unbalanced is syntax trees for parsed languages when the inputs are very large and machine generated. In this case, some language constructs may be repeated very large numbers of times in an unbalanced way. For example, consider the following data structure:

type Expr =
    | Add  of Expr * Expr
    | Bind of string * Expr * Expr
    | Var  of string
    | Num  of int

This data structure would be suitable for representing arithmetic expressions of the forms var, expr + expr, and bind var = expr in expr. Chapters 9 and 11 are dedicated to techniques for representing and processing languages of this kind. As with all tree structures, most traversal algorithms over this type of abstract syntax trees aren't naturally tail recursive. For example, here is a simple evaluator:

type env = Map<string,int>

let rec eval (env: env) expr =
    match expr with
    | Add (e1,e2)         -> eval env e1 + eval env e2
    | Bind (var,rhs,body) -> eval (env.Add(var, eval env rhs)) body
    | Var var             -> env.[var]
    | Num n               -> n

The recursive call eval env rhs isn't tail recursive. For the vast majority of applications, you never need to worry about making this algorithm tail recursive. However, stack overflow may be a problem if bindings are nested to great depth, such as in bind v1 = (bind v2 = . . . (bind v1000000 = 1. . .)) in v1+v1. If the syntax trees come from human-written programs, you can safely assume this won't be the case. But if you need to make the implementation tail recursive, you can use continuations, as shown in Listing 8-12.

Example 8.12. A Tail-Recursive Expression Evaluator Using Continuations

let rec evalCont (env: env) expr cont =
    match expr with
    | Add (e1,e2)         ->
        evalCont env e1 (fun v1 ->
        evalCont env e2 (fun v2 ->
        cont (v1+v2)))
    | Bind (var,rhs,body) ->
        evalCont env rhs (fun v1 ->
        evalCont (env.Add(var,v1)) body cont)
    | Num n             ->
        cont n
    | Var var           ->
        cont (env.[var])

let eval env expr = evalCont env expr (fun x -> x)

Note

Programming with continuations can be tricky, and you should use them only when necessary, or use the F# async type as a way of managing continuation-based code. Where possible, abstract the kind of transformation you're doing on your tree structure (for example, a map, fold, or bottom-up reduction) so you can concentrate on getting the traversal right. In the previous examples, the continuations all effectively play the role of a work list. You can also reprogram your algorithms to use work lists explicitly and to use accumulating parameters for special cases. Sometimes this is necessary to gain maximum efficiency, because an array or a queue can be an optimal representation of a work list. When you make a work list explicit, then the implementation of an algorithm becomes more verbose; but in some cases, debugging can become simpler.

Events

One recurring idiom in .NET programming (and, for example, JavaScript) is that of events. An event is something you can listen to by registering a callback with the event. For example, here's how you can create a WinForms form and listen to mouse clicks on the form:

> open System.Windows.Forms;;
> let form = new Form(Text="Click Form",Visible=true,TopMost=true);;
val form : Form

> form.Click.Add(fun evArgs -> printfn "Clicked!");;
val it : unit = ()

When you run this code in F# Interactive, a window appears; and each time you click the window with the mouse, you see "Clicked!" printed to the console. In .NET terminology, form.Click is an event, and form.Click.Add registers a callback with the event. You can register multiple callbacks with the same event, and many objects publish many events. For example, when you add the following, you see a stream of output when you move the mouse over the form:

> form.MouseMove.Add(fun args -> printfn "Mouse, (X,Y) = (%A,%A)" args.X args.Y);;
val it : unit = ()

If necessary, you can also remove event handlers by first adding them using the AddHandler method and removing them by using RemoveHandler.

The process of clicking the form triggers (or fires) the event, which means the callbacks are called in the order they were registered. Events can't be triggered from the outside. In other words, you can't trigger the Click event on a form; you can only handle it. Events also have event arguments. In the first example shown previously, the event arguments are called evArgs and are ignored. .NET events usually pass arguments of type System.EventArgs or some related type such as System.Windows.Forms.MouseEventArgs or System.Windows.Forms.PaintEventArgs. These arguments generally carry pieces of information; for example, a value of type MouseEventArgs has the properties Button, Clicks, Delta, Location, X, and Y.

Events occur throughout the design of the .NET class libraries. Table 8-2 shows some of the more important events.

Table 8.2. A Selection of Events from the .NET Libraries

Type

Some Sample Events

System.AppDomain

AssemblyLoad, AssemblyResolve, DomainUnload, ProcessExit, UnhandledException (and others)

System.Diagnostics.Process

ErrorDataReceived, Exited, OutputDataReceived (and others)

System.IO.FileSystemWatcher

Changed, Created, Deleted, Error, Renamed (and others)

System.Windows.Forms.Control

BackgroundImageChanged, Click, Disposed, DragDrop, KeyPress, KeyUp, KeyDown, Layout, LostFocus, MouseClick, MouseDown, MouseEnter, MouseHover, MouseLeave, MouseUp, Paint, Resize, TextChanged, Validated, Validating (and others)

System.Windows.Forms.Timer

Tick

System.Timers.Timer

Elapsed

Events as First-Class Values

In F#, an event such as form.Click is a first-class value, which means you can pass it around like any other value. The main advantage this brings is that you can use the combinators in the F# library module Microsoft.FSharp.Control.Event to map, filter, and otherwise transform the event stream in compositional ways. For example, the following code filters the event stream from form.MouseMove so that only events with X > 100 result in output to the console:

form.MouseMove
    |> Event.filter (fun args -> args.X > 100)
    |> Event.listen (fun args -> printfn "Mouse, (X,Y) = (%A,%A)" args.X args.Y)

If you work with events a lot, you find yourself factoring out useful portions of code into functions that preprocess event streams. Table 8-3 shows some of the functions from the F# Event module. One interesting combinator is Event.partition, which splits an event into two events based on a predicate.

Table 8.3. Some Functions from the Event Module

Function

Type

Event.choose

: ('T -> 'U option) -> IEvent<'T> -> IEvent<'U>

Event.create

: unit -> ('T -> unit) * IEvent<'T>

Event.filter

: ('T -> bool) -> IEvent<'T> -> IEvent<'T>

Event.scan

: ('U -> 'T -> 'U) -> 'U -> IEvent<'T> -> IEvent<'U>

Event.listen

: ('T -> unit) -> IEvent<'T> -> unit

Event.map

: ('T -> 'U) -> IEvent<'T> -> IEvent<'U>

Event.partition

: ('T -> bool) -> IEvent<'T> -> IEvent<'T> * IEvent<'T>

Creating and Publishing Events

As you write code in F#, particularly object-oriented code, you need to implement, publish, and trigger events. The normal idiom for doing this is to call new Event<_>(). Listing 8-13 shows how to define an event object that is triggered at random intervals.

Example 8.13. Creating a RandomTicker That Defines, Publishes, and Triggers an Event

open System
open System.Windows.Forms

type RandomTicker(approxInterval) =
    let timer = new Timer()
    let rnd = new System.Random(99)
    let tickEvent = new Event<int> ()

    let chooseInterval() :int =
        approxInterval + approxInterval/4 - rnd.Next(approxInterval/2)

    do timer.Interval <- chooseInterval()

    do timer.Tick.Add(fun args ->
        let interval = chooseInterval()
        tickEvent.Trigger interval;
        timer.Interval <- interval)

    member x.RandomTick = tickEvent.Publish
    member x.Start() = timer.Start()
    member x.Stop() = timer.Stop()
    interface IDisposable with
        member x.Dispose() = timer.Dispose()

Here's how you can instantiate and use this type:

> let rt = new RandomTicker(1000);;
val rt : RandomTicker

> rt.RandomTick.Add(fun nextInterval -> printfn "Tick, next = %A" nextInterval);;
val it : unit = ()

> rt.Start();;
Tick, next = 1072
Tick, next = 927
Tick, next = 765
...
val it : unit = ()

> rt.Stop();;
val it : unit = ()

Events are an idiom understood by all .NET languages. F# event values are immediately compiled in the idiomatic .NET form. This is because F# allows you to go one step further and use events as first-class values. If you need to ensure that your events can be used by other .NET languages, then you should do both of the following:

  • Create the events using new Event<DelegateType, Args> instead of new Event<Args>.

  • Publish the event as a property of a type with the [<CLIEvent>] attribute.

Events are used in most of the later chapters of this book, and you can find many examples there.

Note

Because events allow you to register callbacks, it's sometimes important to be careful about the thread on which an event is being raised. This is particularly true when you're programming with multiple threads or the .NET thread pool. Events are usually fired on the GUI thread of an application. See Chapter 13 for more details about concurrent and multithreaded programming.

Summary

This chapter covered some of the techniques you're likely to use in your day-to-day F# programming, including an in-depth look at hashing, equality, comparison, resource management, tail calls, caching, memoization, and the basics of how F# reveals the wiring for first-class events. The next chapter introduces a final set of language constructs and techniques related to language-oriented programming tasks.

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset